@@ -158,31 +158,56 @@ defmodule Module.Types.Expr do
158158
159159 # %{map | ...}
160160 # TODO: Once we support typed structs, we need to type check them here.
161- # PENDING: here
162- def of_expr ( { :%{} , meta , [ { :| , _ , [ map , args ] } ] } = expr , _expected , _expr , stack , context ) do
163- { map_type , context } = of_expr ( map , @ pending , expr , stack , context )
164-
165- Of . permutate_map ( args , stack , context , & of_expr ( & 1 , @ pending , expr , & 2 , & 3 ) , fn
166- fallback , keys , pairs ->
167- # If there is no fallback (i.e. it is closed), we can update the existing map,
168- # otherwise we only assert the existing keys.
169- keys = if fallback == none ( ) , do: keys , else: Enum . map ( pairs , & elem ( & 1 , 0 ) ) ++ keys
170-
171- # Assert the keys exist
172- Enum . each ( keys , fn key ->
161+ def of_expr ( { :%{} , meta , [ { :| , _ , [ map , args ] } ] } = update , expected , expr , stack , context ) do
162+ # Theoretically we cannot process entries out of order but,
163+ # because all variables are versioned, and Elixir does not
164+ # allow variables defined on the left side of | to be available
165+ # on the right side, this is safe.
166+ { pairs_types , context } =
167+ Of . pairs ( args , expected , stack , context , & of_expr ( & 1 , & 2 , expr , & 3 , & 4 ) )
168+
169+ expected =
170+ if stack . mode == :traversal do
171+ expected
172+ else
173+ # TODO: Once we introduce domain keys, if we ever find a domain
174+ # that overlaps atoms, we can only assume optional(atom()) => term(),
175+ # which is what the `open_map()` below falls back into anyway.
176+ Enum . reduce_while ( pairs_types , expected , fn
177+ { _ , [ key ] , _ } , acc ->
178+ case map_fetch_and_put ( acc , key , term ( ) ) do
179+ { _value , acc } -> { :cont , acc }
180+ _ -> { :halt , open_map ( ) }
181+ end
182+
183+ _ , _ ->
184+ { :halt , open_map ( ) }
185+ end )
186+ end
187+
188+ { map_type , context } = of_expr ( map , expected , expr , stack , context )
189+
190+ try do
191+ Of . permutate_map ( pairs_types , stack , fn fallback , keys_to_assert , pairs ->
192+ # Ensure all keys to assert and all type pairs exist in map
193+ keys_to_assert = Enum . map ( pairs , & elem ( & 1 , 0 ) ) ++ keys_to_assert
194+
195+ Enum . each ( Enum . map ( pairs , & elem ( & 1 , 0 ) ) ++ keys_to_assert , fn key ->
173196 case map_fetch ( map_type , key ) do
174197 { _ , _ } -> :ok
175- :badkey -> throw ( { :badkey , map_type , key , expr , context } )
176- :badmap -> throw ( { :badmap , map_type , expr , context } )
198+ :badkey -> throw ( { :badkey , map_type , key , update , context } )
199+ :badmap -> throw ( { :badmap , map_type , update , context } )
177200 end
178201 end )
179202
203+ # If all keys are known is no fallback (i.e. we know all keys being updated),
204+ # we can update the existing map.
180205 if fallback == none ( ) do
181206 Enum . reduce ( pairs , map_type , fn { key , type } , acc ->
182207 case map_fetch_and_put ( acc , key , type ) do
183208 { _value , descr } -> descr
184- :badkey -> throw ( { :badkey , map_type , key , expr , context } )
185- :badmap -> throw ( { :badmap , map_type , expr , context } )
209+ :badkey -> throw ( { :badkey , map_type , key , update , context } )
210+ :badmap -> throw ( { :badmap , map_type , update , context } )
186211 end
187212 end )
188213 else
@@ -191,51 +216,68 @@ defmodule Module.Types.Expr do
191216 # `keys` deleted.
192217 open_map ( pairs )
193218 end
194- end )
195- catch
196- error -> { error_type ( ) , error ( __MODULE__ , error , meta , stack , context ) }
219+ end )
220+ catch
221+ error -> { error_type ( ) , error ( __MODULE__ , error , meta , stack , context ) }
222+ else
223+ map -> { map , context }
224+ end
197225 end
198226
199227 # %Struct{map | ...}
200- # Note this code, by definition, adds missing struct fields to `map`
201- # because at runtime we do not check for them (only for __struct__ itself).
202- # TODO: Once we support typed structs, we need to type check them here.
203- # PENDING: here
204228 def of_expr (
205- { :% , struct_meta , [ module , { :%{} , _ , [ { :| , update_meta , [ map , args ] } ] } ] } = expr ,
206- _expected ,
207- _expr ,
229+ { :% , struct_meta , [ module , { :%{} , _ , [ { :| , update_meta , [ map , args ] } ] } ] } = struct ,
230+ expected ,
231+ expr ,
208232 stack ,
209233 context
210234 ) do
211- { info , context } = Of . struct_info ( module , struct_meta , stack , context )
212- struct_type = Of . struct_type ( module , info )
213- { map_type , context } = of_expr ( map , @ pending , expr , stack , context )
235+ if stack . mode == :traversal do
236+ { _ , context } = of_expr ( map , term ( ) , struct , stack , context )
214237
215- if disjoint? ( struct_type , map_type ) do
216- warning = { :badstruct , expr , struct_type , map_type , context }
217- { error_type ( ) , error ( __MODULE__ , warning , update_meta , stack , context ) }
218- else
219- map_type = map_put! ( map_type , :__struct__ , atom ( [ module ] ) )
238+ context =
239+ Enum . reduce ( args , context , fn { key , value } , context when is_atom ( key ) ->
240+ { _ , context } = of_expr ( value , term ( ) , expr , stack , context )
241+ context
242+ end )
220243
221- Enum . reduce ( args , { map_type , context } , fn
222- { key , value } , { map_type , context } when is_atom ( key ) ->
223- { value_type , context } = of_expr ( value , @ pending , expr , stack , context )
224- { map_put! ( map_type , key , value_type ) , context }
225- end )
244+ { dynamic ( ) , context }
245+ else
246+ { info , context } = Of . struct_info ( module , struct_meta , stack , context )
247+ struct_type = Of . struct_type ( module , info )
248+ { map_type , context } = of_expr ( map , struct_type , struct , stack , context )
249+
250+ if compatible? ( map_type , struct_type ) do
251+ map_type = map_put! ( map_type , :__struct__ , atom ( [ module ] ) )
252+
253+ Enum . reduce ( args , { map_type , context } , fn
254+ { key , value } , { map_type , context } when is_atom ( key ) ->
255+ # TODO: Once we support typed structs, we need to type check them here.
256+ expected_value_type =
257+ case map_fetch ( expected , key ) do
258+ { _ , expected_value_type } -> expected_value_type
259+ _ -> term ( )
260+ end
261+
262+ { value_type , context } = of_expr ( value , expected_value_type , expr , stack , context )
263+ { map_put! ( map_type , key , value_type ) , context }
264+ end )
265+ else
266+ warning = { :badstruct , struct , struct_type , map_type , context }
267+ { error_type ( ) , error ( __MODULE__ , warning , update_meta , stack , context ) }
268+ end
226269 end
227270 end
228271
229272 # %{...}
230- # PENDING: here
231- def of_expr ( { :%{} , _meta , args } , _expected , expr , stack , context ) do
232- Of . closed_map ( args , stack , context , & of_expr ( & 1 , @ pending , expr , & 2 , & 3 ) )
273+ def of_expr ( { :%{} , _meta , args } , expected , expr , stack , context ) do
274+ Of . closed_map ( args , expected , stack , context , & of_expr ( & 1 , & 2 , expr , & 3 , & 4 ) )
233275 end
234276
235277 # %Struct{}
236- # PENDING: here
237- def of_expr ( { :% , meta , [ module , { :%{} , _ , args } ] } , _expected , expr , stack , context ) do
238- Of . struct_instance ( module , args , meta , stack , context , & of_expr ( & 1 , @ pending , expr , & 2 , & 3 ) )
278+ def of_expr ( { :% , meta , [ module , { :%{} , _ , args } ] } , expected , expr , stack , context ) do
279+ fun = & of_expr ( & 1 , & 2 , expr , & 3 , & 4 )
280+ Of . struct_instance ( module , args , expected , meta , stack , context , fun )
239281 end
240282
241283 # ()
@@ -575,8 +617,7 @@ defmodule Module.Types.Expr do
575617 # to avoid export dependencies. So we do it here.
576618 if Code . ensure_loaded? ( exception ) and function_exported? ( exception , :__struct__ , 0 ) do
577619 { info , context } = Of . struct_info ( exception , meta , stack , context )
578- # TODO: For properly defined structs, this should not be dynamic
579- { dynamic ( Of . struct_type ( exception , info , args ) ) , context }
620+ { Of . struct_type ( exception , info , args ) , context }
580621 else
581622 # If the exception cannot be found or is invalid, fetch the signature to emit warnings.
582623 { _ , context } = Apply . signature ( exception , :__struct__ , 0 , meta , stack , context )
@@ -694,8 +735,8 @@ defmodule Module.Types.Expr do
694735
695736 ## General helpers
696737
697- defp apply_local ( fun , args , _expected , { _ , meta , _ } = expr , stack , context ) do
698- { local_info , domain , context } = Apply . local_domain ( fun , args , meta , stack , context )
738+ defp apply_local ( fun , args , expected , { _ , meta , _ } = expr , stack , context ) do
739+ { local_info , domain , context } = Apply . local_domain ( fun , args , expected , meta , stack , context )
699740
700741 { args_types , context } =
701742 zip_map_reduce ( args , domain , context , & of_expr ( & 1 , & 2 , expr , stack , & 3 ) )
0 commit comments