@@ -158,104 +158,132 @@ defmodule Module.Types.Infer do
158158 end
159159 end
160160
161- defp unify_maps ( source_pairs , target_pairs , % { context: :pattern } = stack , context ) do
161+ # * All required keys on each side need to match to the other side.
162+ # * All optional keys on each side that do not match must be discarded.
163+
164+ defp unify_maps ( source_pairs , target_pairs , stack , context ) do
162165 source_pairs = expand_struct ( source_pairs )
163166 target_pairs = expand_struct ( target_pairs )
164167
165- # Since maps in patterns only support literal keys (excluding maps)
166- # we can do exact type match without subtype checking
167-
168- unique_right_pairs =
169- Enum . reject ( target_pairs , fn { _kind , key , _value } ->
170- List . keyfind ( source_pairs , key , 1 )
171- end )
172-
173- unique_pairs = source_pairs ++ unique_right_pairs
174-
175- # Build union of all unique key-value pairs between the maps
176- result =
177- map_reduce_ok ( unique_pairs , context , fn { source_kind , source_key , source_value } , context ->
178- case List . keyfind ( target_pairs , source_key , 1 ) do
179- { target_kind , ^ source_key , target_value } ->
180- case unify ( source_value , target_value , stack , context ) do
181- { :ok , value , context } ->
182- { :ok , { unify_kinds ( source_kind , target_kind ) , source_key , value } , context }
183-
184- { :error , reason } ->
185- { :error , reason }
186- end
187-
188- nil ->
189- { :ok , { source_kind , source_key , source_value } , context }
190- end
191- end )
168+ { source_required , source_optional } = split_pairs ( source_pairs )
169+ { target_required , target_optional } = split_pairs ( target_pairs )
170+
171+ with { :ok , source_required_pairs , context } <-
172+ unify_source_required ( source_required , target_pairs , stack , context ) ,
173+ { :ok , target_required_pairs , context } <-
174+ unify_target_required ( target_required , source_pairs , stack , context ) ,
175+ { :ok , source_optional_pairs , context } <-
176+ unify_source_optional ( source_optional , target_optional , stack , context ) ,
177+ { :ok , target_optional_pairs , context } <-
178+ unify_target_optional ( target_optional , source_optional , stack , context ) ,
179+ pairs =
180+ [
181+ source_required_pairs ,
182+ target_required_pairs ,
183+ source_optional_pairs ,
184+ target_optional_pairs
185+ ]
186+ |> Enum . concat ( )
187+ # Remove duplicate pairs from matching in both left and right directions
188+ |> Enum . uniq ( )
189+ |> simplify_struct ( ) do
190+ { :ok , { :map , pairs } , context }
191+ else
192+ { :error , :unify } ->
193+ error ( { :unable_unify , { :map , source_pairs } , { :map , target_pairs } } , stack , context )
192194
193- case result do
194- { :ok , pairs , context } -> { :ok , { :map , simplify_struct ( pairs ) } , context }
195- { :error , reason } -> { :error , reason }
195+ { :error , context } ->
196+ { :error , context }
196197 end
197198 end
198199
199- defp unify_maps ( source_pairs , target_pairs , % { context: :expr } = stack , context ) do
200- source_pairs = expand_struct ( source_pairs )
201- target_pairs = expand_struct ( target_pairs )
200+ defp unify_source_required ( source_required , target_pairs , stack , context ) do
201+ map_reduce_ok ( source_required , context , fn { source_key , source_value } , context ->
202+ Enum . find_value ( target_pairs , fn { target_kind , target_key , target_value } ->
203+ with { :ok , key , context } <- unify ( source_key , target_key , stack , context ) do
204+ case unify ( source_value , target_value , stack , context ) do
205+ { :ok , value , context } ->
206+ { :ok , { :required , key , value } , context }
202207
203- result =
204- flat_map_reduce_ok ( source_pairs , context , fn { source_kind , _ , _ } = source_pair , context ->
205- # Currently we only match on exact and dynamic types
206- # since those are the only we get from map.key
207- with :error <- exact_map_match ( source_pair , target_pairs , stack , context ) ,
208- :error <- dynamic_map_match ( source_pair , target_pairs , stack , context ) do
209- if source_kind == :optional do
210- { :ok , [ ] , context }
211- else
212- source_map = { :map , simplify_struct ( source_pairs ) }
213- target_map = { :map , simplify_struct ( target_pairs ) }
214- error ( { :unable_unify , source_map , target_map } , stack , context )
208+ { :error , _reason } ->
209+ source_map = { :map , [ { :required , source_key , source_value } ] }
210+ target_map = { :map , [ { target_kind , target_key , target_value } ] }
211+ error ( { :unable_unify , source_map , target_map } , stack , context )
215212 end
213+ else
214+ { :error , _reason } -> nil
216215 end
217- end )
216+ end ) || { :error , :unify }
217+ end )
218+ end
218219
219- case result do
220- { :ok , pairs , context } ->
221- pairs = Enum . uniq_by ( pairs ++ target_pairs , fn { _kind , key , _value } -> key end )
222- { :ok , { :map , simplify_struct ( pairs ) } , context }
220+ defp unify_target_required ( target_required , source_pairs , stack , context ) do
221+ map_reduce_ok ( target_required , context , fn { target_key , target_value } , context ->
222+ Enum . find_value ( source_pairs , fn { source_kind , source_key , source_value } ->
223+ with { :ok , key , context } <- unify ( source_key , target_key , stack , context ) do
224+ case unify ( source_value , target_value , stack , context ) do
225+ { :ok , value , context } ->
226+ { :ok , { :required , key , value } , context }
223227
224- { :error , reason } ->
225- { :error , reason }
226- end
228+ { :error , _reason } ->
229+ source_map = { :map , [ { source_kind , source_key , source_value } ] }
230+ target_map = { :map , [ { :required , target_key , target_value } ] }
231+ error ( { :unable_unify , source_map , target_map } , stack , context )
232+ end
233+ else
234+ { :error , _reason } -> nil
235+ end
236+ end ) || { :error , :unify }
237+ end )
227238 end
228239
229- defp exact_map_match ( { source_kind , source_key , source_value } , target_pairs , stack , context ) do
230- case List . keyfind ( target_pairs , source_key , 1 ) do
231- { target_kind , ^ source_key , target_value } ->
232- case unify ( source_value , target_value , stack , context ) do
233- { :ok , value , context } ->
234- { :ok , [ { unify_kinds ( source_kind , target_kind ) , source_key , value } ] , context }
240+ defp unify_source_optional ( source_optional , target_optional , stack , context ) do
241+ flat_map_reduce_ok ( source_optional , context , fn { source_key , source_value } , context ->
242+ Enum . find_value ( target_optional , fn { target_key , target_value } ->
243+ with { :ok , key , context } <- unify ( source_key , target_key , stack , context ) do
244+ case unify ( source_value , target_value , stack , context ) do
245+ { :ok , value , context } ->
246+ { :ok , [ { :optional , key , value } ] , context }
235247
236- { :error , reason } ->
237- { :error , reason }
248+ { :error , _reason } ->
249+ source_map = { :map , [ { :optional , source_key , source_value } ] }
250+ target_map = { :map , [ { :optional , target_key , target_value } ] }
251+ error ( { :unable_unify , source_map , target_map } , stack , context )
252+ end
253+ else
254+ _ -> nil
238255 end
239-
240- nil ->
241- :error
242- end
256+ end ) || { :ok , [ ] , context }
257+ end )
243258 end
244259
245- defp dynamic_map_match ( { source_kind , source_key , source_value } , target_pairs , stack , context ) do
246- case dynamic_pair ( target_pairs ) do
247- { :ok , { _target_kind , target_value } } ->
248- case unify ( source_value , target_value , stack , context ) do
249- { :ok , value , context } ->
250- { :ok , [ { source_kind , source_key , value } ] , context }
260+ defp unify_target_optional ( target_optional , source_optional , stack , context ) do
261+ flat_map_reduce_ok ( target_optional , context , fn { target_key , target_value } , context ->
262+ Enum . find_value ( source_optional , fn { source_key , source_value } ->
263+ with { :ok , key , context } <- unify ( source_key , target_key , stack , context ) do
264+ case unify ( source_value , target_value , stack , context ) do
265+ { :ok , value , context } ->
266+ { :ok , [ { :optional , key , value } ] , context }
251267
252- { :error , reason } ->
253- { :error , reason }
268+ { :error , _reason } ->
269+ source_map = { :map , [ { :optional , source_key , source_value } ] }
270+ target_map = { :map , [ { :optional , target_key , target_value } ] }
271+ error ( { :unable_unify , source_map , target_map } , stack , context )
272+ end
273+ else
274+ _ -> nil
254275 end
276+ end ) || { :ok , [ ] , context }
277+ end )
278+ end
255279
256- :error ->
257- :error
258- end
280+ defp split_pairs ( pairs ) do
281+ { required , optional } =
282+ Enum . split_with ( pairs , fn { kind , _key , _value } -> kind == :required end )
283+
284+ required = Enum . map ( required , fn { _kind , key , value } -> { key , value } end )
285+ optional = Enum . map ( optional , fn { _kind , key , value } -> { key , value } end )
286+ { required , optional }
259287 end
260288
261289 @ doc """
@@ -467,6 +495,8 @@ defmodule Module.Types.Infer do
467495 def unify_kinds ( :optional , :optional ) , do: :optional
468496
469497 # Collect relevant information from context and traces to report error
498+ # TODO: We should do this lazily since in some cases unification will error
499+ # but we continue attempting unifying other types
470500 defp error ( { :unable_unify , left , right } , stack , context ) do
471501 { fun , arity } = context . function
472502 line = get_meta ( stack . last_expr ) [ :line ]
@@ -491,13 +521,11 @@ defmodule Module.Types.Infer do
491521 |> Enum . uniq ( )
492522
493523 Enum . flat_map ( stack , fn var_index ->
494- case Map . fetch ( context . traces , var_index ) do
495- { :ok , traces } ->
496- expr_var = Map . fetch! ( context . types_to_vars , var_index )
497- Enum . map ( traces , & { expr_var , & 1 } )
498-
499- _other ->
500- [ ]
524+ with % { ^ var_index => traces } <- context . traces ,
525+ % { ^ var_index => expr_var } <- context . types_to_vars do
526+ Enum . map ( traces , & { expr_var , & 1 } )
527+ else
528+ _other -> [ ]
501529 end
502530 end )
503531 end
@@ -564,17 +592,11 @@ defmodule Module.Types.Infer do
564592 end
565593 end
566594
595+ # TODO: Resolve type variables if %{__struct__: var, ...}
567596 defp fetch_struct_pair ( pairs ) do
568597 case Enum . find ( pairs , & match? ( { :required , { :atom , :__struct__ } , { :atom , _ } } , & 1 ) ) do
569598 { :required , { :atom , :__struct__ } , { :atom , module } } -> { :ok , module }
570599 nil -> :error
571600 end
572601 end
573-
574- defp dynamic_pair ( pairs ) do
575- case List . keyfind ( pairs , :dynamic , 1 ) do
576- { kind , :dynamic , type } -> { :ok , { kind , type } }
577- nil -> :error
578- end
579- end
580602end
0 commit comments