@@ -303,9 +303,6 @@ defmodule Module.Types.Descr do
303303 end
304304 end
305305
306- defp optional_static? ( % { optional: _ } ) , do: true
307- defp optional_static? ( _ ) , do: false
308-
309306 defp remove_optional_static ( % { } = descr ) , do: Map . delete ( descr , :optional )
310307 defp remove_optional_static ( descr ) , do: descr
311308
@@ -2744,116 +2741,137 @@ defmodule Module.Types.Descr do
27442741 end
27452742
27462743 @ doc """
2747- Updates the `key_descr` with `type`.
2744+ Updates `key_descr` in `descr ` with `type`.
27482745
27492746 `key_descr` is split into optional and required keys and tracked accordingly.
2747+ The gradual aspect of `key_descr` does not impact the return type.
2748+
2749+ It returns `{type, descr, errors}`, `:badmap`, `{:error, errors}`.
2750+ The list of `errors` may be empty, which implies the a bad domain.
2751+ The `return_type?` flag is used for optimizations purposes. If set to false,
2752+ the returned `type` should not be used, as it will be imprecise.
27502753 """
2751- def map_update ( :term , _key_descr , _type ) , do: :badmap
2754+ def map_update ( descr , key_descr , type , return_type? \\ true )
2755+
2756+ def map_update ( :term , _key_descr , _type , _return_type? ) , do: :badmap
27522757
2753- def map_update ( descr , key_descr , :term ) ,
2754- do: map_update_static_value ( descr , key_descr , :term )
2758+ def map_update ( descr , key_descr , :term , return_type? ) ,
2759+ do: map_update_static_value ( descr , key_descr , :term , return_type? )
27552760
2756- def map_update ( descr , key_descr , type ) do
2761+ def map_update ( descr , key_descr , type , return_type? ) do
27572762 case :maps . take ( :dynamic , type ) do
2758- :error -> map_update_static_value ( descr , key_descr , type )
2759- { dynamic , _static } -> map_update_static_value ( dynamic ( descr ) , key_descr , dynamic )
2763+ :error ->
2764+ map_update_static_value ( descr , key_descr , type , return_type? )
2765+
2766+ { dynamic , _static } ->
2767+ map_update_static_value ( dynamic ( descr ) , key_descr , dynamic , return_type? )
27602768 end
27612769 end
27622770
2763- defp map_update_static_value ( descr , key_descr , type ) do
2771+ defp map_update_static_value ( descr , key_descr , type , return_type? ) do
27642772 split_keys = map_split_keys_and_domains ( key_descr )
27652773
27662774 case :maps . take ( :dynamic , descr ) do
27672775 :error ->
27682776 if descr_key? ( descr , :map ) and map_only? ( descr ) do
2769- with { :ok , { _type , descr } } <-
2770- map_update_static ( descr , split_keys , type , fn type ->
2771- { optional? , type } = pop_optional_static ( type )
2772- optional? or empty? ( type )
2773- end ) do
2774- if descr == none ( ) do
2775- { :baddomain , key_descr }
2776- else
2777- { :ok , descr }
2778- end
2777+ { type , descr , errors } =
2778+ map_update_static ( descr , split_keys , type , return_type? , fn optional? , type ->
2779+ optional? or empty? ( type )
2780+ end )
2781+
2782+ if descr == none ( ) do
2783+ { :error , errors }
2784+ else
2785+ { type , descr , errors }
27792786 end
27802787 else
27812788 :badmap
27822789 end
27832790
27842791 { dynamic , static } ->
27852792 if descr_key? ( dynamic , :map ) and map_only? ( static ) do
2786- with { :ok , { _static_value , static_descr } } <-
2787- map_update_static ( static , split_keys , type , & optional_static? / 1 ) ,
2788- { :ok , { _dynamic_value , dynamic_descr } } <-
2789- map_update_static ( dynamic , split_keys , type , & empty_or_optional? / 1 ) do
2790- if dynamic_descr == none ( ) do
2791- { :baddomain , key_descr }
2792- else
2793- { :ok , union ( static_descr , dynamic ( dynamic_descr ) ) }
2794- end
2793+ { static_value , static_descr , static_errors } =
2794+ map_update_static ( static , split_keys , type , return_type? , fn optional? , _ ->
2795+ optional?
2796+ end )
2797+
2798+ { dynamic_value , dynamic_descr , dynamic_errors } =
2799+ map_update_static ( dynamic , split_keys , type , return_type? , fn _ , type ->
2800+ empty? ( type )
2801+ end )
2802+
2803+ if dynamic_descr == none ( ) do
2804+ { :error , static_errors ++ dynamic_errors }
2805+ else
2806+ { union ( static_value , dynamic ( dynamic_value ) ) ,
2807+ union ( static_descr , dynamic ( dynamic_descr ) ) , static_errors ++ dynamic_errors }
27952808 end
27962809 else
27972810 :badmap
27982811 end
27992812 end
28002813 end
28012814
2802- defp map_update_static ( % { map: bdd } , split_keys , type , missing_fun ) do
2815+ defp map_update_static ( % { map: bdd } , split_keys , type , return_type? , missing_fun ) do
28032816 { required_keys , optional_keys , maybe_negated_set , required_domains , optional_domains } =
28042817 split_keys
28052818
2806- bdd = map_update_put_negated ( bdd , maybe_negated_set , type )
28072819 dnf = map_bdd_to_dnf ( bdd )
28082820
2809- callback = fn ->
2810- # If we have required keys, we can assume domain_atom always work
2811- if required_keys != [ ] do
2812- true
2821+ callback =
2822+ if return_type? do
2823+ fn -> map_update_merge_atom_key ( bdd , dnf ) end
28132824 else
2814- map_update_any_atom_key ( bdd , dnf )
2825+ fn ->
2826+ # If we have required keys, we can assume domain_atom always work
2827+ if required_keys != [ ] or map_update_any_atom_key? ( bdd , dnf ) do
2828+ term ( )
2829+ else
2830+ none ( )
2831+ end
2832+ end
28152833 end
2816- end
28172834
2818- case map_update_get_domains ( dnf , required_domains , none ( ) , callback ) do
2819- { found_required? , required_domains , [ ] , value } ->
2820- # Optional domains can be missing
2821- { found_optional? , optional_domains , _ , value } =
2822- map_update_get_domains ( dnf , optional_domains , value , callback )
2835+ # Required domains must be found
2836+ { found_required? , required_domains , missing_domains , value } =
2837+ map_update_get_domains ( dnf , required_domains , none ( ) , return_type? , callback )
28232838
2824- acc =
2825- if found_optional? or found_required? do
2826- # If any of required or optional domains are satisfied, then we compute the
2827- # initial return type. `map_update_keys_static` will then union into the
2828- # computed type below, using the original bdd/dnf, not the one with updated domains.
2829- descr = map_update_put_domains ( bdd , required_domains ++ optional_domains , type )
2830- { value , descr }
2831- else
2832- { value , none ( ) }
2833- end
2839+ # Optional domains can be missing
2840+ { found_optional? , optional_domains , _ , value } =
2841+ map_update_get_domains ( dnf , optional_domains , value , return_type? , callback )
28342842
2835- map_update_keys_static ( dnf , required_keys , optional_keys , type , missing_fun , acc )
2843+ bdd = map_update_put_negated ( bdd , maybe_negated_set , type )
2844+ errors = Enum . map ( missing_domains , & { :baddomain , domain_key_to_descr ( & 1 ) } )
28362845
2837- { _ , _ , [ missing_domain | _ ] , _ } ->
2838- { :baddomain , domain_key_to_descr ( missing_domain ) }
2839- end
2846+ acc =
2847+ if found_optional? or found_required? do
2848+ # If any of required or optional domains are satisfied, then we compute the
2849+ # initial return type. `map_update_keys_static` will then union into the
2850+ # computed type below, using the original bdd/dnf, not the one with updated domains.
2851+ descr = map_update_put_domains ( bdd , required_domains ++ optional_domains , type )
2852+ { remove_optional ( value ) , descr , errors }
2853+ else
2854+ { remove_optional ( value ) , none ( ) , errors }
2855+ end
2856+
2857+ map_update_keys_static ( dnf , required_keys , optional_keys , type , missing_fun , acc )
28402858 end
28412859
2842- defp map_update_static ( % { } , _split_keys , _type , _missing_fun ) do
2843- { :ok , { none ( ) , none ( ) } }
2860+ defp map_update_static ( % { } , _split_keys , _type , _return_type? , _missing_fun ) do
2861+ { none ( ) , none ( ) , [ ] }
28442862 end
28452863
2846- defp map_update_static ( :term , split_keys , type , missing_fun ) do
2864+ defp map_update_static ( :term , split_keys , type , _return_type? , missing_fun ) do
28472865 # Since it is an open map, we don't need to check the domains.
28482866 # The negated set will also be empty, because there are no fields.
28492867 # Finally, merged required_keys into optional_keys.
28502868 { required_keys , optional_keys , _maybe_negated_set , required_domains , optional_domains } =
28512869 split_keys
28522870
28532871 if required_domains != [ ] or optional_domains != [ ] do
2854- { :ok , { term ( ) , open_map ( ) } }
2872+ { term ( ) , open_map ( ) , [ ] }
28552873 else
2856- acc = { none ( ) , none ( ) }
2874+ acc = { none ( ) , none ( ) , [ ] }
28572875 dnf = map_bdd_to_dnf ( @ map_top )
28582876 map_update_keys_static ( dnf , required_keys , optional_keys , type , missing_fun , acc )
28592877 end
@@ -2862,26 +2880,25 @@ defmodule Module.Types.Descr do
28622880 defp map_update_keys_static ( dnf , required , optional , type , missing_fun , acc ) do
28632881 acc = map_update_keys ( dnf , required , type , :required , missing_fun , acc )
28642882 acc = map_update_keys ( dnf , optional , type , :optional , missing_fun , acc )
2865- { :ok , acc }
2866- catch
2867- { :badkey , key } -> { :badkey , key }
2883+ acc
28682884 end
28692885
28702886 defp map_update_keys ( dnf , keys , type , required_or_optional , missing_fun , acc ) do
2871- Enum . reduce ( keys , acc , fn key , { acc_value , acc_descr } ->
2887+ Enum . reduce ( keys , acc , fn key , { acc_value , acc_descr , acc_errors } ->
28722888 { value , descr } = map_dnf_pop_key_static ( dnf , key , none ( ) )
2889+ { optional? , value } = pop_optional_static ( value )
28732890
28742891 cond do
2875- not missing_fun . ( value ) ->
2892+ not missing_fun . ( optional? , value ) ->
28762893 acc_value = union ( value , acc_value )
28772894 acc_descr = union ( map_put_key_static ( descr , key , type ) , acc_descr )
2878- { acc_value , acc_descr }
2895+ { acc_value , acc_descr , acc_errors }
28792896
28802897 required_or_optional == :required ->
2881- throw ( { :badkey , key } )
2898+ { acc_value , acc_descr , [ { :badkey , key } | acc_errors ] }
28822899
28832900 true ->
2884- { acc_value , acc_descr }
2901+ { acc_value , acc_descr , acc_errors }
28852902 end
28862903 end )
28872904 end
@@ -2951,7 +2968,23 @@ defmodule Module.Types.Descr do
29512968 end )
29522969 end
29532970
2954- defp map_update_any_atom_key ( bdd , dnf ) do
2971+ defp map_update_merge_atom_key ( bdd , dnf ) do
2972+ { _seen , acc } =
2973+ bdd_reduce ( bdd , { % { } , none ( ) } , fn { _tag , fields } , seen_acc ->
2974+ Enum . reduce ( fields , seen_acc , fn { key , _type } , { seen , acc } ->
2975+ if Map . has_key? ( seen , key ) do
2976+ { seen , acc }
2977+ else
2978+ { _ , value } = map_dnf_fetch_static ( dnf , key )
2979+ { Map . put ( seen , key , [ ] ) , union ( acc , value ) }
2980+ end
2981+ end )
2982+ end )
2983+
2984+ acc
2985+ end
2986+
2987+ defp map_update_any_atom_key? ( bdd , dnf ) do
29552988 bdd_reduce ( bdd , % { } , fn { _tag , fields } , acc ->
29562989 Enum . reduce ( fields , acc , fn { key , _type } , acc ->
29572990 if Map . has_key? ( acc , key ) do
@@ -2967,16 +3000,30 @@ defmodule Module.Types.Descr do
29673000 :found_key -> true
29683001 end
29693002
2970- defp map_update_get_domains ( dnf , domain_keys , acc , any_atom_key ) do
3003+ defp map_update_get_domains ( dnf , domain_keys , acc , require_type? , any_atom_key ) do
29713004 Enum . reduce ( domain_keys , { false , [ ] , [ ] , acc } , fn domain_key , { found? , valid , invalid , acc } ->
29723005 value = map_get_domain ( dnf , domain_key , none ( ) )
29733006
29743007 cond do
2975- not empty_or_optional? ( value ) ->
2976- { true , [ domain_key | valid ] , invalid , union ( acc , value ) }
3008+ domain_key == :atom ->
3009+ atom_acc = any_atom_key . ( )
3010+
3011+ cond do
3012+ not empty_or_optional? ( value ) ->
3013+ acc = if require_type? , do: union ( union ( atom_acc , acc ) , value ) , else: acc
3014+ { true , [ :atom | valid ] , invalid , acc }
3015+
3016+ not empty_or_optional? ( atom_acc ) ->
3017+ acc = if require_type? , do: union ( atom_acc , acc ) , else: acc
3018+ { true , valid , [ :atom | invalid ] , acc }
3019+
3020+ true ->
3021+ { found? , valid , [ :atom | invalid ] , acc }
3022+ end
29773023
2978- domain_key == :atom and any_atom_key . ( ) ->
2979- { true , valid , [ domain_key | invalid ] , acc }
3024+ not empty_or_optional? ( value ) ->
3025+ acc = if require_type? , do: union ( acc , value ) , else: acc
3026+ { true , [ domain_key | valid ] , invalid , acc }
29803027
29813028 true ->
29823029 { found? , valid , [ domain_key | invalid ] , acc }
0 commit comments