@@ -114,38 +114,36 @@ defmodule Module.Types.Expr do
114114 end
115115
116116 # %{map | ...}
117+ # TODO: Once we support typed structs, we need to type check them here.
117118 def of_expr ( { :%{} , _ , [ { :| , _ , [ map , args ] } ] } , stack , context ) do
118- { _args_type , context } = Of . closed_map ( args , stack , context , & of_expr / 3 )
119- { _map_type , context } = of_expr ( map , stack , context )
120- # TODO: intersect map with keys of terms for args
121- # TODO: Merge args_type into map_type with dynamic/static key requirement
122- { dynamic ( open_map ( ) ) , context }
119+ { map_type , context } = of_expr ( map , stack , context )
120+ Of . update_map ( map_type , args , stack , context , & of_expr / 3 )
123121 end
124122
125123 # %Struct{map | ...}
124+ # Note this code, by definition, adds missing struct fields to `map`
125+ # because at runtime we do not check for them (only for __struct__ itself).
126+ # TODO: Once we support typed structs, we need to type check them here.
126127 def of_expr (
127128 { :% , struct_meta , [ module , { :%{} , _ , [ { :| , update_meta , [ map , args ] } ] } ] } = expr ,
128129 stack ,
129130 context
130131 ) do
131- { args_types , context } =
132- Enum . map_reduce ( args , context , fn { key , value } , context when is_atom ( key ) ->
133- { type , context } = of_expr ( value , stack , context )
134- { { key , type } , context }
135- end )
136-
137- # TODO: args_types could be an empty list
138- { struct_type , context } =
139- Of . struct ( module , args_types , :only_defaults , struct_meta , stack , context )
140-
132+ { info , context } = Of . struct_info ( module , struct_meta , stack , context )
133+ struct_type = Of . struct_type ( module , info )
141134 { map_type , context } = of_expr ( map , stack , context )
142135
143136 if disjoint? ( struct_type , map_type ) do
144137 warning = { :badupdate , :struct , expr , struct_type , map_type , context }
145138 { error_type ( ) , error ( __MODULE__ , warning , update_meta , stack , context ) }
146139 else
147- # TODO: Merge args_type into map_type with dynamic/static key requirement
148- Of . struct ( module , args_types , :merge_defaults , struct_meta , stack , context )
140+ map_type = map_put! ( map_type , :__struct__ , atom ( [ module ] ) )
141+
142+ Enum . reduce ( args , { map_type , context } , fn
143+ { key , value } , { map_type , context } when is_atom ( key ) ->
144+ { value_type , context } = of_expr ( value , stack , context )
145+ { map_put! ( map_type , key , value_type ) , context }
146+ end )
149147 end
150148 end
151149
@@ -155,9 +153,8 @@ defmodule Module.Types.Expr do
155153 end
156154
157155 # %Struct{}
158- def of_expr ( { :% , _ , [ module , { :%{} , _ , args } ] } = expr , stack , context ) do
159- # TODO: We should not skip defaults
160- Of . struct ( expr , module , args , :skip_defaults , stack , context , & of_expr / 3 )
156+ def of_expr ( { :% , meta , [ module , { :%{} , _ , args } ] } , stack , context ) do
157+ Of . struct_instance ( module , args , meta , stack , context , & of_expr / 3 )
161158 end
162159
163160 # ()
@@ -357,7 +354,8 @@ defmodule Module.Types.Expr do
357354 # Exceptions are not validated in the compiler,
358355 # to avoid export dependencies. So we do it here.
359356 if Code . ensure_loaded? ( exception ) and function_exported? ( exception , :__struct__ , 0 ) do
360- Of . struct ( exception , args , :merge_defaults , meta , stack , context )
357+ { info , context } = Of . struct_info ( exception , meta , stack , context )
358+ { Of . struct_type ( exception , info , args ) , context }
361359 else
362360 # If the exception cannot be found or is invalid,
363361 # we call Of.remote/5 to emit a warning.
@@ -493,6 +491,13 @@ defmodule Module.Types.Expr do
493491 context
494492 end
495493
494+ defp map_put! ( map_type , key , value_type ) do
495+ case map_put ( map_type , key , value_type ) do
496+ descr when is_descr ( descr ) -> descr
497+ error -> raise "unexpected #{ inspect ( error ) } "
498+ end
499+ end
500+
496501 ## Warning formatting
497502
498503 def format_diagnostic ( { :badupdate , type , expr , expected_type , actual_type , context } ) do
0 commit comments