@@ -24,105 +24,6 @@ defmodule Module.Types.Pattern do
2424 of_pattern ( pattern , % { stack | context: :pattern } , context )
2525 end
2626
27- # :atom
28- def of_pattern ( atom , _stack , context ) when is_atom ( atom ) do
29- { :ok , { :atom , atom } , context }
30- end
31-
32- # 12
33- def of_pattern ( literal , _stack , context ) when is_integer ( literal ) do
34- { :ok , :integer , context }
35- end
36-
37- # 1.2
38- def of_pattern ( literal , _stack , context ) when is_float ( literal ) do
39- { :ok , :float , context }
40- end
41-
42- # "..."
43- def of_pattern ( literal , _stack , context ) when is_binary ( literal ) do
44- { :ok , :binary , context }
45- end
46-
47- # <<...>>>
48- def of_pattern ( { :<<>> , _meta , args } , stack , context ) do
49- result = Of . binary ( args , stack , context , & of_pattern / 3 )
50-
51- case result do
52- { :ok , context } -> { :ok , :binary , context }
53- { :error , reason } -> { :error , reason }
54- end
55- end
56-
57- # left | []
58- def of_pattern ( { :| , _meta , [ left_expr , [ ] ] } = expr , stack , context ) do
59- stack = push_expr_stack ( expr , stack )
60- of_pattern ( left_expr , stack , context )
61- end
62-
63- # left | right
64- def of_pattern ( { :| , _meta , [ left_expr , right_expr ] } = expr , stack , context ) do
65- stack = push_expr_stack ( expr , stack )
66-
67- case of_pattern ( left_expr , stack , context ) do
68- { :ok , left , context } ->
69- case of_pattern ( right_expr , stack , context ) do
70- { :ok , { :list , right } , context } ->
71- { :ok , to_union ( [ left , right ] , context ) , context }
72-
73- { :ok , right , context } ->
74- { :ok , to_union ( [ left , right ] , context ) , context }
75-
76- { :error , reason } ->
77- { :error , reason }
78- end
79-
80- { :error , reason } ->
81- { :error , reason }
82- end
83- end
84-
85- # []
86- def of_pattern ( [ ] , _stack , context ) do
87- { :ok , { :list , :dynamic } , context }
88- end
89-
90- # [expr, ...]
91- def of_pattern ( exprs , stack , context ) when is_list ( exprs ) do
92- stack = push_expr_stack ( exprs , stack )
93-
94- case map_reduce_ok ( exprs , context , & of_pattern ( & 1 , stack , & 2 ) ) do
95- { :ok , types , context } -> { :ok , { :list , to_union ( types , context ) } , context }
96- { :error , reason } -> { :error , reason }
97- end
98- end
99-
100- # left ++ right
101- def of_pattern (
102- { { :. , _meta1 , [ :erlang , :++ ] } , _meta2 , [ left_expr , right_expr ] } = expr ,
103- stack ,
104- context
105- ) do
106- stack = push_expr_stack ( expr , stack )
107-
108- case of_pattern ( left_expr , stack , context ) do
109- { :ok , { :list , left } , context } ->
110- case of_pattern ( right_expr , stack , context ) do
111- { :ok , { :list , right } , context } ->
112- { :ok , { :list , to_union ( [ left , right ] , context ) } , context }
113-
114- { :ok , right , context } ->
115- { :ok , { :list , to_union ( [ left , right ] , context ) } , context }
116-
117- { :error , reason } ->
118- { :error , reason }
119- end
120-
121- { :error , reason } ->
122- { :error , reason }
123- end
124- end
125-
12627 # _
12728 def of_pattern ( { :_ , _meta , atom } , _stack , context ) when is_atom ( atom ) do
12829 { :ok , :dynamic , context }
@@ -139,21 +40,6 @@ defmodule Module.Types.Pattern do
13940 { :ok , type , context }
14041 end
14142
142- # {left, right}
143- def of_pattern ( { left , right } , stack , context ) do
144- of_pattern ( { :{} , [ ] , [ left , right ] } , stack , context )
145- end
146-
147- # {...}
148- def of_pattern ( { :{} , _meta , exprs } = expr , stack , context ) do
149- stack = push_expr_stack ( expr , stack )
150-
151- case map_reduce_ok ( exprs , context , & of_pattern ( & 1 , stack , & 2 ) ) do
152- { :ok , types , context } -> { :ok , { :tuple , length ( types ) , types } , context }
153- { :error , reason } -> { :error , reason }
154- end
155- end
156-
15743 # left = right
15844 def of_pattern ( { := , _meta , [ left_expr , right_expr ] } = expr , stack , context ) do
15945 stack = push_expr_stack ( expr , stack )
@@ -163,23 +49,6 @@ defmodule Module.Types.Pattern do
16349 do: unify ( left_type , right_type , stack , context )
16450 end
16551
166- # %{...}
167- def of_pattern ( { :%{} , _meta , args } = expr , stack , context ) do
168- stack = push_expr_stack ( expr , stack )
169- Of . open_map ( args , stack , context , & of_pattern / 3 )
170- end
171-
172- # %Struct{...}
173- def of_pattern ( { :% , meta1 , [ module , { :%{} , _meta2 , args } ] } = expr , stack , context )
174- when is_atom ( module ) do
175- stack = push_expr_stack ( expr , stack )
176-
177- with { :ok , struct , context } <- Of . struct ( module , meta1 , context ) ,
178- { :ok , map , context } <- Of . open_map ( args , stack , context , & of_pattern / 3 ) do
179- unify ( map , struct , stack , context )
180- end
181- end
182-
18352 # %_{...}
18453 def of_pattern (
18554 { :% , _meta1 , [ { :_ , _meta2 , var_context } , { :%{} , _meta3 , args } ] } = expr ,
@@ -195,7 +64,8 @@ defmodule Module.Types.Pattern do
19564 end
19665
19766 # %var{...} and %^var{...}
198- def of_pattern ( { :% , _meta1 , [ var , { :%{} , _meta2 , args } ] } = expr , stack , context ) do
67+ def of_pattern ( { :% , _meta1 , [ var , { :%{} , _meta2 , args } ] } = expr , stack , context )
68+ when not is_atom ( var ) do
19969 stack = push_expr_stack ( expr , stack )
20070
20171 with { :ok , var_type , context } = of_pattern ( var , stack , context ) ,
@@ -205,6 +75,10 @@ defmodule Module.Types.Pattern do
20575 end
20676 end
20777
78+ def of_pattern ( expr , stack , context ) do
79+ of_shared ( expr , stack , context , & of_pattern / 3 )
80+ end
81+
20882 def unify_kinds ( :required , _ ) , do: :required
20983 def unify_kinds ( _ , :required ) , do: :required
21084 def unify_kinds ( :optional , :optional ) , do: :optional
@@ -401,10 +275,8 @@ defmodule Module.Types.Pattern do
401275 { :ok , type , context }
402276 end
403277
404- # other literals
405278 def of_guard ( expr , stack , context ) do
406- # Fall back to of_pattern/3 for literals
407- of_pattern ( expr , stack , context )
279+ of_shared ( expr , stack , context , & of_guard / 3 )
408280 end
409281
410282 defp fresh_context ( context ) do
@@ -550,4 +422,136 @@ defmodule Module.Types.Pattern do
550422 defp type_guard? ( name ) do
551423 name in @ type_guards
552424 end
425+
426+ ## Shared
427+
428+ # :atom
429+ defp of_shared ( atom , _stack , context , _fun ) when is_atom ( atom ) do
430+ { :ok , { :atom , atom } , context }
431+ end
432+
433+ # 12
434+ defp of_shared ( literal , _stack , context , _fun ) when is_integer ( literal ) do
435+ { :ok , :integer , context }
436+ end
437+
438+ # 1.2
439+ defp of_shared ( literal , _stack , context , _fun ) when is_float ( literal ) do
440+ { :ok , :float , context }
441+ end
442+
443+ # "..."
444+ defp of_shared ( literal , _stack , context , _fun ) when is_binary ( literal ) do
445+ { :ok , :binary , context }
446+ end
447+
448+ # <<...>>>
449+ defp of_shared ( { :<<>> , _meta , args } , stack , context , fun ) do
450+ case Of . binary ( args , stack , context , fun ) do
451+ { :ok , context } -> { :ok , :binary , context }
452+ { :error , reason } -> { :error , reason }
453+ end
454+ end
455+
456+ # left | []
457+ defp of_shared ( { :| , _meta , [ left_expr , [ ] ] } = expr , stack , context , fun ) do
458+ stack = push_expr_stack ( expr , stack )
459+ fun . ( left_expr , stack , context )
460+ end
461+
462+ # left | right
463+ defp of_shared ( { :| , _meta , [ left_expr , right_expr ] } = expr , stack , context , fun ) do
464+ stack = push_expr_stack ( expr , stack )
465+
466+ case fun . ( left_expr , stack , context ) do
467+ { :ok , left , context } ->
468+ case fun . ( right_expr , stack , context ) do
469+ { :ok , { :list , right } , context } ->
470+ { :ok , to_union ( [ left , right ] , context ) , context }
471+
472+ { :ok , right , context } ->
473+ { :ok , to_union ( [ left , right ] , context ) , context }
474+
475+ { :error , reason } ->
476+ { :error , reason }
477+ end
478+
479+ { :error , reason } ->
480+ { :error , reason }
481+ end
482+ end
483+
484+ # []
485+ defp of_shared ( [ ] , _stack , context , _fun ) do
486+ { :ok , { :list , :dynamic } , context }
487+ end
488+
489+ # [expr, ...]
490+ defp of_shared ( exprs , stack , context , fun ) when is_list ( exprs ) do
491+ stack = push_expr_stack ( exprs , stack )
492+
493+ case map_reduce_ok ( exprs , context , & fun . ( & 1 , stack , & 2 ) ) do
494+ { :ok , types , context } -> { :ok , { :list , to_union ( types , context ) } , context }
495+ { :error , reason } -> { :error , reason }
496+ end
497+ end
498+
499+ # left ++ right
500+ defp of_shared (
501+ { { :. , _meta1 , [ :erlang , :++ ] } , _meta2 , [ left_expr , right_expr ] } = expr ,
502+ stack ,
503+ context ,
504+ fun
505+ ) do
506+ stack = push_expr_stack ( expr , stack )
507+
508+ case fun . ( left_expr , stack , context ) do
509+ { :ok , { :list , left } , context } ->
510+ case fun . ( right_expr , stack , context ) do
511+ { :ok , { :list , right } , context } ->
512+ { :ok , { :list , to_union ( [ left , right ] , context ) } , context }
513+
514+ { :ok , right , context } ->
515+ { :ok , { :list , to_union ( [ left , right ] , context ) } , context }
516+
517+ { :error , reason } ->
518+ { :error , reason }
519+ end
520+
521+ { :error , reason } ->
522+ { :error , reason }
523+ end
524+ end
525+
526+ # {left, right}
527+ defp of_shared ( { left , right } , stack , context , fun ) do
528+ of_shared ( { :{} , [ ] , [ left , right ] } , stack , context , fun )
529+ end
530+
531+ # {...}
532+ defp of_shared ( { :{} , _meta , exprs } = expr , stack , context , fun ) do
533+ stack = push_expr_stack ( expr , stack )
534+
535+ case map_reduce_ok ( exprs , context , & fun . ( & 1 , stack , & 2 ) ) do
536+ { :ok , types , context } -> { :ok , { :tuple , length ( types ) , types } , context }
537+ { :error , reason } -> { :error , reason }
538+ end
539+ end
540+
541+ # %{...}
542+ defp of_shared ( { :%{} , _meta , args } = expr , stack , context , fun ) do
543+ stack = push_expr_stack ( expr , stack )
544+ Of . open_map ( args , stack , context , fun )
545+ end
546+
547+ # %Struct{...}
548+ defp of_shared ( { :% , meta1 , [ module , { :%{} , _meta2 , args } ] } = expr , stack , context , fun )
549+ when is_atom ( module ) do
550+ stack = push_expr_stack ( expr , stack )
551+
552+ with { :ok , struct , context } <- Of . struct ( module , meta1 , context ) ,
553+ { :ok , map , context } <- Of . open_map ( args , stack , context , fun ) do
554+ unify ( map , struct , stack , context )
555+ end
556+ end
553557end
0 commit comments