@@ -3,6 +3,7 @@ defmodule Module.Types do
33
44 alias Module.Types . { Descr , Expr , Pattern }
55
6+ # TODO: Local captures
67 # TODO: Inference of tail recursion
78 # TODO: Checking of unused private functions/clauses
89
@@ -12,90 +13,52 @@ defmodule Module.Types do
1213 @ doc false
1314 def infer ( module , file , defs , env ) do
1415 finder = & List . keyfind ( defs , & 1 , 0 )
15- handler = & infer_signature_for ( & 1 , & 2 , module , file , finder , env )
16- context = context ( { handler , % { } } )
16+ handler = & local_handler ( & 1 , & 2 , & 3 , finder )
17+ stack = stack ( :infer , file , module , { :__info__ , 1 } , :all , env , handler )
18+ context = context ( % { } )
1719
1820 { types , _context } =
1921 for { fun_arity , kind , _meta , _clauses } = def <- defs ,
2022 kind == :def and fun_arity not in @ no_infer ,
2123 reduce: { [ ] , context } do
2224 { types , context } ->
23- { _kind , inferred , context } =
24- infer_signature_for ( fun_arity , context , module , file , fn _ -> def end , env )
25-
25+ { _kind , inferred , context } = local_handler ( fun_arity , stack , context , fn _ -> def end )
2626 { [ { fun_arity , inferred } | types ] , context }
2727 end
2828
2929 Map . new ( types )
3030 end
3131
32- defp infer_signature_for ( fun_arity , context , module , file , finder , env ) do
33- case context . local_handler do
34- { _ , % { ^ fun_arity => { kind , inferred } } } ->
35- { kind , inferred , context }
36-
37- { _ , _ } ->
38- { { fun , arity } , kind , _meta , clauses } = finder . ( fun_arity )
39- expected = List . duplicate ( Descr . dynamic ( ) , arity )
40-
41- stack = stack ( :infer , file , module , fun_arity , :all , env )
42- context = update_local_state ( context , & Map . put ( & 1 , fun_arity , { kind , :none } ) )
43-
44- { pair_types , context } =
45- Enum . reduce ( clauses , { [ ] , context } , fn
46- { meta , args , guards , body } , { inferred , context } ->
47- context = context ( context . local_handler )
48-
49- try do
50- { args_types , context } =
51- Pattern . of_head ( args , guards , expected , :default , meta , stack , context )
52-
53- { return_type , context } = Expr . of_expr ( body , stack , context )
54- { add_inferred ( inferred , args_types , return_type , [ ] ) , context }
55- rescue
56- e ->
57- internal_error! ( e , __STACKTRACE__ , kind , meta , module , fun , args , guards , body )
58- end
59- end )
60-
61- inferred = { :infer , Enum . reverse ( pair_types ) }
62- { kind , inferred , update_local_state ( context , & Map . put ( & 1 , fun_arity , { kind , inferred } ) ) }
63- end
64- end
65-
6632 @ doc false
6733 def warnings ( module , file , defs , no_warn_undefined , cache ) do
6834 finder = & List . keyfind ( defs , & 1 , 0 )
69- handler = & warnings_for ( & 1 , & 2 , module , file , finder , no_warn_undefined , cache )
70- context = context ( { handler , % { } } )
35+ handler = & local_handler ( & 1 , & 2 , & 3 , finder )
36+ stack = stack ( :dynamic , file , module , { :__info__ , 1 } , no_warn_undefined , cache , handler )
37+ context = context ( % { } )
7138
7239 context =
7340 Enum . reduce ( defs , context , fn { fun_arity , _kind , _meta , _clauses } = def , context ->
74- finder = fn _ -> def end
75-
76- { _kind , _inferred , context } =
77- warnings_for ( fun_arity , context , module , file , finder , no_warn_undefined , cache )
78-
41+ { _kind , _inferred , context } = local_handler ( fun_arity , stack , context , fn _ -> def end )
7942 context
8043 end )
8144
8245 context . warnings
8346 end
8447
85- defp warnings_for ( fun_arity , context , module , file , finder , no_warn_undefined , cache ) do
86- case context . local_handler do
87- { _ , % { ^ fun_arity => { kind , inferred } } } ->
48+ defp local_handler ( fun_arity , stack , context , finder ) do
49+ case context . local_state do
50+ % { ^ fun_arity => { kind , inferred } } ->
8851 { kind , inferred , context }
8952
90- { _ , _ } ->
91- { { fun , arity } , kind , meta , clauses } = finder . ( fun_arity )
92- expected = List . duplicate ( Descr . dynamic ( ) , arity )
53+ local_state ->
54+ { { fun , arity } , kind , meta , clauses } =
55+ finder . ( fun_arity ) || raise "could not find #{ inspect ( fun_arity ) } "
9356
94- file = with_file_meta ( meta , file )
95- stack = stack ( :dynamic , file , module , fun_arity , no_warn_undefined , cache )
96- context = update_local_state ( context , & Map . put ( & 1 , fun_arity , { kind , :none } ) )
57+ expected = List . duplicate ( Descr . dynamic ( ) , arity )
58+ stack = stack |> fresh_stack ( fun_arity ) |> with_file_meta ( meta )
59+ context = put_in ( context . local_state , Map . put ( local_state , fun_arity , { kind , :none } ) )
9760
98- { pair_types , context } =
61+ { clauses_types , clauses_context } =
9962 Enum . reduce ( clauses , { [ ] , context } , fn
10063 { meta , args , guards , body } , { inferred , context } ->
10164 context = fresh_context ( context )
@@ -108,12 +71,13 @@ defmodule Module.Types do
10871 { add_inferred ( inferred , args_types , return_type , [ ] ) , context }
10972 rescue
11073 e ->
111- internal_error! ( e , __STACKTRACE__ , kind , meta , module , fun , args , guards , body )
74+ internal_error! ( e , __STACKTRACE__ , kind , meta , fun , args , guards , body , stack )
11275 end
11376 end )
11477
115- inferred = { :infer , Enum . reverse ( pair_types ) }
116- { kind , inferred , update_local_state ( context , & Map . put ( & 1 , fun_arity , { kind , inferred } ) ) }
78+ inferred = { :infer , Enum . reverse ( clauses_types ) }
79+ context = update_in ( context . local_state , & Map . put ( & 1 , fun_arity , { kind , inferred } ) )
80+ { kind , inferred , restore_context ( context , clauses_context ) }
11781 end
11882 end
11983
@@ -128,19 +92,19 @@ defmodule Module.Types do
12892 defp add_inferred ( [ ] , args , return , acc ) ,
12993 do: [ { args , return } | Enum . reverse ( acc ) ]
13094
131- defp with_file_meta ( meta , file ) do
95+ defp with_file_meta ( stack , meta ) do
13296 case Keyword . fetch ( meta , :file ) do
133- { :ok , { meta_file , _ } } -> meta_file
134- :error -> file
97+ { :ok , { meta_file , _ } } -> % { stack | file: meta_file }
98+ :error -> stack
13599 end
136100 end
137101
138- defp internal_error! ( e , stack , kind , meta , module , fun , args , guards , body ) do
102+ defp internal_error! ( e , trace , kind , meta , fun , args , guards , body , stack ) do
139103 def_expr = { kind , meta , [ guards_to_expr ( guards , { fun , [ ] , args } ) , [ do: body ] ] }
140104
141105 exception =
142106 RuntimeError . exception ( """
143- found error while checking types for #{ Exception . format_mfa ( module , fun , length ( args ) ) } :
107+ found error while checking types for #{ Exception . format_mfa ( stack . module , fun , length ( args ) ) } :
144108
145109 #{ Exception . format_banner ( :error , e , stack ) } \
146110
@@ -151,7 +115,7 @@ defmodule Module.Types do
151115 Please report this bug at: https://github.com/elixir-lang/elixir/issues
152116 """ )
153117
154- reraise exception , stack
118+ reraise exception , trace
155119 end
156120
157121 defp guards_to_expr ( [ ] , left ) do
@@ -163,7 +127,7 @@ defmodule Module.Types do
163127 end
164128
165129 @ doc false
166- def stack ( mode , file , module , function , no_warn_undefined , cache )
130+ def stack ( mode , file , module , function , no_warn_undefined , cache , handler )
167131 when mode in [ :static , :dynamic , :infer ] do
168132 % {
169133 # The fallback meta used for literals in patterns and guards
@@ -200,31 +164,37 @@ defmodule Module.Types do
200164 # We may also want for applications with subtyping in dynamic mode to always
201165 # intersect with dynamic, but this mode may be too lax (to be decided based on
202166 # feedback).
203- mode: mode
167+ mode: mode ,
168+ # The function for handling local calls
169+ local_handler: handler
204170 }
205171 end
206172
207173 @ doc false
208- def context ( local_handler , warnings \\ [ ] ) do
174+ def context ( local_state ) do
209175 % {
210176 # A list of all warnings found so far
211- warnings: warnings ,
177+ warnings: [ ] ,
212178 # All vars and their types
213179 vars: % { } ,
214180 # Variables and arguments from patterns
215181 pattern_info: nil ,
216182 # If type checking has found an error/failure
217183 failed: false ,
218- # Local handler
219- local_handler: local_handler
184+ # Local state
185+ local_state: local_state
220186 }
221187 end
222188
223- defp fresh_context ( % { local_handler: local_handler , warnings: warnings } ) do
224- context ( local_handler , warnings )
189+ defp fresh_stack ( stack , function ) do
190+ % { stack | function: function }
191+ end
192+
193+ defp fresh_context ( context ) do
194+ % { context | vars: % { } , failed: false }
225195 end
226196
227- defp update_local_state ( % { local_handler: { handler , state } } = context , fun ) do
228- % { context | local_handler: { handler , fun . ( state ) } }
197+ defp restore_context ( % { vars: vars , failed: failed } , later_context ) do
198+ % { later_context | vars: vars , failed: failed }
229199 end
230200end
0 commit comments