@@ -241,46 +241,51 @@ defmodule Module.Types.Expr do
241241 |> dynamic_unless_static ( stack )
242242 end
243243
244- # TODO: case expr do pat -> expr end
245244 def of_expr ( { :case , _meta , [ case_expr , [ { :do , clauses } ] ] } , stack , context ) do
246- { _expr_type , context } = of_expr ( case_expr , stack , context )
245+ { expr_type , context } = of_expr ( case_expr , stack , context )
247246
248247 clauses
249- |> of_clauses ( stack , { none ( ) , context } )
248+ |> of_clauses ( stack , [ expr_type ] , { none ( ) , context } )
250249 |> dynamic_unless_static ( stack )
251250 end
252251
253252 # TODO: fn pat -> expr end
254253 def of_expr ( { :fn , _meta , clauses } , stack , context ) do
255- { _acc , context } = of_clauses ( clauses , stack , { none ( ) , context } )
254+ [ { :-> , _ , [ args , _ ] } | _ ] = clauses
255+ expected = Enum . map ( args , fn _ -> dynamic ( ) end )
256+ { _acc , context } = of_clauses ( clauses , stack , expected , { none ( ) , context } )
256257 { fun ( ) , context }
257258 end
258259
259- @ try_blocks [ :do , :after ]
260- @ try_clause_blocks [ :catch , :else ]
260+ def of_expr ( { :try , _meta , [ [ do: body ] ++ blocks ] } , stack , context ) do
261+ { body_type , context } = of_expr ( body , stack , context )
262+ initial = if Keyword . has_key? ( blocks , :else ) , do: none ( ) , else: body_type
261263
262- # TODO: try do expr end
263- def of_expr ( { :try , _meta , [ blocks ] } , stack , context ) do
264- context =
265- Enum . reduce ( blocks , context , fn
266- { :rescue , clauses } , context ->
267- Enum . reduce ( clauses , context , fn
268- { :-> , _ , [ [ { :in , meta , [ var , exceptions ] } = expr ] , body ] } , context ->
269- of_rescue ( var , exceptions , body , expr , [ ] , meta , stack , context )
270-
271- { :-> , meta , [ [ var ] , body ] } , context ->
272- of_rescue ( var , [ ] , body , var , [ :anonymous_rescue ] , meta , stack , context )
273- end )
264+ blocks
265+ |> Enum . reduce ( { initial , context } , fn
266+ { :rescue , clauses } , acc_context ->
267+ Enum . reduce ( clauses , acc_context , fn
268+ { :-> , _ , [ [ { :in , meta , [ var , exceptions ] } = expr ] , body ] } , { acc , context } ->
269+ { type , context } = of_rescue ( var , exceptions , body , expr , [ ] , meta , stack , context )
270+ { union ( type , acc ) , context }
271+
272+ { :-> , meta , [ [ var ] , body ] } , { acc , context } ->
273+ hint = [ :anonymous_rescue ]
274+ { type , context } = of_rescue ( var , [ ] , body , var , hint , meta , stack , context )
275+ { union ( type , acc ) , context }
276+ end )
274277
275- { block , body } , context when block in @ try_blocks ->
276- of_expr_context ( body , stack , context )
278+ { :after , body } , { acc , context } ->
279+ { _type , context } = of_expr ( body , stack , context )
280+ { acc , context }
277281
278- { block , clauses } , context when block in @ try_clause_blocks ->
279- { _ , context } = of_clauses ( clauses , stack , { none ( ) , context } )
280- context
281- end )
282+ { :catch , clauses } , acc_context ->
283+ of_clauses ( clauses , stack , [ atom ( [ :error , :exit , :throw ] ) , dynamic ( ) ] , acc_context )
282284
283- { dynamic ( ) , context }
285+ { :else , clauses } , acc_context ->
286+ of_clauses ( clauses , stack , [ body_type ] , acc_context )
287+ end )
288+ |> dynamic_unless_static ( stack )
284289 end
285290
286291 def of_expr ( { :receive , _meta , [ blocks ] } , stack , context ) do
@@ -290,7 +295,7 @@ defmodule Module.Types.Expr do
290295 { acc , context }
291296
292297 { :do , clauses } , { acc , context } ->
293- of_clauses ( clauses , stack , { acc , context } )
298+ of_clauses ( clauses , stack , [ dynamic ( ) ] , { acc , context } )
294299
295300 { :after , [ { :-> , meta , [ [ timeout ] , body ] } ] } , { acc , context } ->
296301 { timeout_type , context } = of_expr ( timeout , stack , context )
@@ -313,7 +318,7 @@ defmodule Module.Types.Expr do
313318 context = Enum . reduce ( opts , context , & for_option ( & 1 , stack , & 2 ) )
314319
315320 if Keyword . has_key? ( opts , :reduce ) do
316- { _ , context } = of_clauses ( block , stack , { none ( ) , context } )
321+ { _ , context } = of_clauses ( block , stack , [ dynamic ( ) ] , { none ( ) , context } )
317322 { dynamic ( ) , context }
318323 else
319324 { _type , context } = of_expr ( block , stack , context )
@@ -431,7 +436,7 @@ defmodule Module.Types.Expr do
431436 context
432437 end
433438
434- of_expr_context ( body , stack , context )
439+ of_expr ( body , stack , context )
435440 end
436441
437442 ## Comprehensions
@@ -456,15 +461,18 @@ defmodule Module.Types.Expr do
456461 end
457462
458463 defp for_clause ( expr , stack , context ) do
459- of_expr_context ( expr , stack , context )
464+ { _type , context } = of_expr ( expr , stack , context )
465+ context
460466 end
461467
462468 defp for_option ( { :into , expr } , stack , context ) do
463- of_expr_context ( expr , stack , context )
469+ { _type , context } = of_expr ( expr , stack , context )
470+ context
464471 end
465472
466473 defp for_option ( { :reduce , expr } , stack , context ) do
467- of_expr_context ( expr , stack , context )
474+ { _type , context } = of_expr ( expr , stack , context )
475+ context
468476 end
469477
470478 defp for_option ( { :uniq , _ } , _stack , context ) do
@@ -482,15 +490,17 @@ defmodule Module.Types.Expr do
482490 end
483491
484492 defp with_clause ( expr , stack , context ) do
485- of_expr_context ( expr , stack , context )
493+ { _type , context } = of_expr ( expr , stack , context )
494+ context
486495 end
487496
488497 defp with_option ( { :do , body } , stack , context ) do
489- of_expr_context ( body , stack , context )
498+ { _type , context } = of_expr ( body , stack , context )
499+ context
490500 end
491501
492502 defp with_option ( { :else , clauses } , stack , context ) do
493- { _ , context } = of_clauses ( clauses , stack , { none ( ) , context } )
503+ { _ , context } = of_clauses ( clauses , stack , [ dynamic ( ) ] , { none ( ) , context } )
494504 context
495505 end
496506
@@ -522,7 +532,7 @@ defmodule Module.Types.Expr do
522532 defp dynamic_unless_static ( { _ , _ } = output , % { mode: :static } ) , do: output
523533 defp dynamic_unless_static ( { type , context } , % { mode: _ } ) , do: { dynamic ( type ) , context }
524534
525- defp of_clauses ( clauses , stack , acc_context ) do
535+ defp of_clauses ( clauses , stack , _expected , acc_context ) do
526536 Enum . reduce ( clauses , acc_context , fn { :-> , meta , [ head , body ] } , { acc , context } ->
527537 { patterns , guards } = extract_head ( head )
528538 { _types , context } = Pattern . of_head ( patterns , guards , meta , stack , context )
@@ -545,11 +555,6 @@ defmodule Module.Types.Expr do
545555 defp flatten_when ( { :when , _meta , [ left , right ] } ) , do: [ left | flatten_when ( right ) ]
546556 defp flatten_when ( other ) , do: [ other ]
547557
548- defp of_expr_context ( expr , stack , context ) do
549- { _type , context } = of_expr ( expr , stack , context )
550- context
551- end
552-
553558 defp map_put! ( map_type , key , value_type ) do
554559 case map_put ( map_type , key , value_type ) do
555560 { :ok , descr } -> descr
0 commit comments