@@ -32,21 +32,21 @@ defmodule Module.Types.Infer do
3232 end
3333
3434 defp do_unify ( type , { :var , var } , stack , context ) do
35- case Map . fetch! ( context . types , var ) do
36- { :var , var_type } ->
35+ case context . types do
36+ % { ^ var => { :var , var_type } } ->
3737 do_unify ( type , { :var , var_type } , stack , context )
3838
39- _other ->
39+ % { } ->
4040 unify_var ( var , type , stack , context , _var_source = false )
4141 end
4242 end
4343
4444 defp do_unify ( { :var , var } , type , stack , context ) do
45- case Map . fetch! ( context . types , var ) do
46- { :var , var_type } ->
45+ case context . types do
46+ % { ^ var => { :var , var_type } } ->
4747 do_unify ( { :var , var_type } , type , stack , context )
4848
49- _other ->
49+ % { } ->
5050 unify_var ( var , type , stack , context , _var_source = true )
5151 end
5252 end
@@ -84,10 +84,17 @@ defmodule Module.Types.Infer do
8484 end
8585
8686 defp do_unify ( source , target , stack , context ) do
87- if subtype? ( source , target , context ) do
88- { :ok , source , context }
89- else
90- error ( :unable_unify , { source , target , stack } , context )
87+ cond do
88+ # This condition exists to handle unions with unbound vars.
89+ # TODO: handle unions properly.
90+ has_unbound_var? ( source , context ) or has_unbound_var? ( target , context ) ->
91+ { :ok , source , context }
92+
93+ subtype? ( source , target , context ) ->
94+ { :ok , source , context }
95+
96+ true ->
97+ error ( :unable_unify , { source , target , stack } , context )
9198 end
9299 end
93100
@@ -96,8 +103,8 @@ defmodule Module.Types.Infer do
96103 end
97104
98105 defp unify_var ( var , type , stack , context , var_source? ) do
99- case Map . fetch! ( context . types , var ) do
100- :unbound ->
106+ case context . types do
107+ % { ^ var => :unbound } ->
101108 context = refine_var ( var , type , stack , context )
102109 stack = push_unify_stack ( var , stack )
103110
@@ -111,7 +118,7 @@ defmodule Module.Types.Infer do
111118 { :ok , { :var , var } , context }
112119 end
113120
114- var_type ->
121+ % { ^ var => var_type } ->
115122 # Only add trace if the variable wasn't already "expanded"
116123 context =
117124 if variable_expanded? ( var , stack , context ) do
@@ -268,13 +275,15 @@ defmodule Module.Types.Infer do
268275 If the variable has already been added, return the existing type variable.
269276 """
270277 def new_var ( var , context ) do
271- case Map . fetch ( context . vars , var_name ( var ) ) do
272- { :ok , type } ->
278+ var_name = var_name ( var )
279+
280+ case context . vars do
281+ % { ^ var_name => type } ->
273282 { type , context }
274283
275- :error ->
284+ % { } ->
276285 type = { :var , context . counter }
277- vars = Map . put ( context . vars , var_name ( var ) , type )
286+ vars = Map . put ( context . vars , var_name , type )
278287 types_to_vars = Map . put ( context . types_to_vars , context . counter , var )
279288 types = Map . put ( context . types , context . counter , :unbound )
280289 traces = Map . put ( context . traces , context . counter , [ ] )
@@ -312,7 +321,16 @@ defmodule Module.Types.Infer do
312321 { type , context }
313322 end
314323
315- def resolve_var ( { :var , var } , context ) , do: resolve_var ( Map . fetch! ( context . types , var ) , context )
324+ @ doc """
325+ Resolves a variable raising if it is unbound.
326+ """
327+ def resolve_var ( { :var , var } , context ) do
328+ case context . types do
329+ % { ^ var => :unbound } -> raise "cannot resolve unbound var"
330+ % { ^ var => type } -> resolve_var ( type , context )
331+ end
332+ end
333+
316334 def resolve_var ( other , _context ) , do: other
317335
318336 # Check unify stack to see if variable was already expanded
@@ -321,15 +339,15 @@ defmodule Module.Types.Infer do
321339 end
322340
323341 defp variable_same? ( left , right , context ) do
324- case Map . fetch ( context . types , left ) do
325- { :ok , { :var , new_left } } ->
342+ case context . types do
343+ % { ^ left => { :var , new_left } } ->
326344 variable_same? ( new_left , right , context )
327345
328- _ ->
329- case Map . fetch ( context . types , right ) do
330- { :ok , { :var , new_right } } -> variable_same? ( left , new_right , context )
331- _ -> false
332- end
346+ % { ^ right => { :var , new_right } } ->
347+ variable_same? ( left , new_right , context )
348+
349+ % { } ->
350+ false
333351 end
334352 end
335353
@@ -370,11 +388,11 @@ defmodule Module.Types.Infer do
370388 # Bad: `{var} = var`
371389 # Good: `x = y; y = z; z = x`
372390 defp recursive_type? ( { :var , var } = parent , parents , context ) do
373- case Map . fetch! ( context . types , var ) do
374- :unbound ->
391+ case context . types do
392+ % { ^ var => :unbound } ->
375393 false
376394
377- type ->
395+ % { ^ var => type } ->
378396 if type in parents do
379397 not Enum . all? ( parents , & match? ( { :var , _ } , & 1 ) )
380398 else
@@ -402,31 +420,69 @@ defmodule Module.Types.Infer do
402420 false
403421 end
404422
423+ @ doc """
424+ Checks if the type has a type var.
425+ """
426+ def has_unbound_var? ( { :var , var } , context ) do
427+ case context . types do
428+ % { ^ var => :unbound } -> true
429+ % { ^ var => type } -> has_unbound_var? ( type , context )
430+ end
431+ end
432+
433+ def has_unbound_var? ( { :tuple , args } , context ) ,
434+ do: Enum . any? ( args , & has_unbound_var? ( & 1 , context ) )
435+
436+ def has_unbound_var? ( { :union , args } , context ) ,
437+ do: Enum . any? ( args , & has_unbound_var? ( & 1 , context ) )
438+
439+ def has_unbound_var? ( _type , _context ) , do: false
440+
405441 @ doc """
406442 Checks if the first argument is a subtype of the second argument.
407- Only checks for simple and concrete types.
443+
444+ This function assumes that:
445+
446+ * dynamic is not considered a subtype of all other types but the top type
447+ * unbound variables are not subtype of anything
448+
408449 """
409450 # TODO: boolean <: false | true
410451 # TODO: number <: float | integer
452+ # TODO: implement subtype for maps
453+ def subtype? ( type , type , _context ) , do: true
454+
455+ def subtype? ( { :var , var } , other , context ) do
456+ case context . types do
457+ % { ^ var => :unbound } -> false
458+ % { ^ var => type } -> subtype? ( type , other , context )
459+ end
460+ end
461+
462+ def subtype? ( other , { :var , var } , context ) do
463+ case context . types do
464+ % { ^ var => :unbound } -> false
465+ % { ^ var => type } -> subtype? ( other , type , context )
466+ end
467+ end
468+
469+ def subtype? ( _ , :dynamic , _context ) , do: true
411470 def subtype? ( { :atom , boolean } , :boolean , _context ) when is_boolean ( boolean ) , do: true
412471 def subtype? ( { :atom , atom } , :atom , _context ) when is_atom ( atom ) , do: true
413472 def subtype? ( :boolean , :atom , _context ) , do: true
414473 def subtype? ( :float , :number , _context ) , do: true
415474 def subtype? ( :integer , :number , _context ) , do: true
416475 def subtype? ( { :tuple , _ } , :tuple , _context ) , do: true
417476
418- # TODO: Lift unions to unify/3?
419- def subtype? ( { :union , left_types } , { :union , right_types } = right_union , context ) do
420- # Since we can't unify unions we give up when encountering variables
421- Enum . any? ( left_types ++ right_types , & match? ( { :var , _ } , & 1 ) ) or
422- Enum . all? ( left_types , & subtype? ( & 1 , right_union , context ) )
477+ def subtype? ( { :union , left_types } , { :union , _ } = right_union , context ) do
478+ Enum . all? ( left_types , & subtype? ( & 1 , right_union , context ) )
423479 end
424480
425481 def subtype? ( left , { :union , right_types } , context ) do
426482 Enum . any? ( right_types , & subtype? ( left , & 1 , context ) )
427483 end
428484
429- def subtype? ( left , right , _context ) , do: left == right
485+ def subtype? ( _left , _right , _context ) , do: false
430486
431487 @ doc """
432488 Returns a "simplified" union using `subtype?/3` to remove redundant types.
@@ -436,17 +492,14 @@ defmodule Module.Types.Infer do
436492 `{boolean()} | {atom()}` will not be merged or types with variables that
437493 are distinct but equivalent such as `a | b when a ~ b`.
438494 """
439- # TODO: Translate union of all top types to dynamic()
495+ def to_union ( [ type ] , _context ) , do: type
496+
440497 def to_union ( types , context ) when types != [ ] do
441498 flat_types = flatten_union ( types )
442499
443- if :dynamic in flat_types do
444- :dynamic
445- else
446- case unique_super_types ( flat_types , context ) do
447- [ type ] -> type
448- types -> { :union , types }
449- end
500+ case unique_super_types ( flat_types , context ) do
501+ [ type ] -> type
502+ types -> { :union , types }
450503 end
451504 end
452505
0 commit comments