diff options
author | Björn-Egil Dahlberg <[email protected]> | 2014-01-29 11:15:46 +0100 |
---|---|---|
committer | Björn-Egil Dahlberg <[email protected]> | 2014-01-29 11:15:46 +0100 |
commit | cb50354a9d3463cf07b830ecf28260adc5b361c0 (patch) | |
tree | 4794bac549046c2b1039ec0ac559b955ad3b31fc /lib/stdlib/src/erl_lint.erl | |
parent | d960d54f75c51b81a99a1c5cf40c19f2e9d55068 (diff) | |
parent | cf5bc2e917dbcb2c2841bf07b995efe105bea4be (diff) | |
download | otp-cb50354a9d3463cf07b830ecf28260adc5b361c0.tar.gz otp-cb50354a9d3463cf07b830ecf28260adc5b361c0.tar.bz2 otp-cb50354a9d3463cf07b830ecf28260adc5b361c0.zip |
Merge branch 'egil/maps/OTP-11616'
* egil/maps/OTP-11616: (112 commits)
compiler: Add core compile test for maps
compiler: Fix core parse for Maps
compiler: Fixup #map_pair{} spec
erts: Strengthen map_SUITE tests
erts: Update maps_fold test to respect maps:fold/3
stdlib: Make maps:fold/3 order-independent
erts: Fixup enif_make_map_put on windows
erts: Update preloaded erts_internal.beam
hipe: Fixup update cerl pretty printer
erts: Add map construction to driver API
dialyzer: Add maps tests
dialyzer: Remove dead code
dialyzer: Reflect map_pair core changes in dialyzer
hipe: Update cerl pretty printer
compiler: Update inliner tests
compiler: Squash #c_map_pair_*{} to #c_map_pair{}
compiler: Squash #k_map_pair_*{} to #k_map_pair{}
preloaded: Fixup export cmp_term in erts_internal
erts: Change 'size' argument of enif_get_map_size from int* to size_t*
erts: Fix compile error for halfword emulator
...
Diffstat (limited to 'lib/stdlib/src/erl_lint.erl')
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 66 |
1 files changed, 66 insertions, 0 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index f0d50df4c7..f630db6032 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -225,6 +225,8 @@ format_error({too_many_arguments,Arity}) -> "maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]); %% --- patterns and guards --- format_error(illegal_pattern) -> "illegal pattern"; +format_error({illegal_map_key_variable,K}) -> + io_lib:format("illegal use of variable ~w in map",[K]); format_error(illegal_bin_pattern) -> "binary patterns cannot be matched in parallel using '='"; format_error(illegal_expr) -> "illegal expression"; @@ -232,6 +234,9 @@ format_error({illegal_guard_local_call, {F,A}}) -> io_lib:format("call to local/imported function ~w/~w is illegal in guard", [F,A]); format_error(illegal_guard_expr) -> "illegal guard expression"; +%% --- maps --- +format_error(illegal_map_construction) -> + "only association operators '=>' are allowed in map construction"; %% --- records --- format_error({undefined_record,T}) -> io_lib:format("record ~w undefined", [T]); @@ -1366,6 +1371,19 @@ pattern({cons,_Line,H,T}, Vt, Old, Bvt, St0) -> {vtmerge_pat(Hvt, Tvt),vtmerge_pat(Bvt1,Bvt2),St2}; pattern({tuple,_Line,Ps}, Vt, Old, Bvt, St) -> pattern_list(Ps, Vt, Old, Bvt, St); +pattern({map,_Line,Ps}, Vt, Old, Bvt, St) -> + pattern_list(Ps, Vt, Old, Bvt, St); +pattern({map_field_assoc,Line,_,_}, _, _, _, St) -> + {[],[],add_error(Line, illegal_pattern, St)}; +pattern({map_field_exact,Line,KP,VP}, Vt, Old, Bvt0, St0) -> + %% if the key pattern has variables we should fail + case expr(KP,[],St0) of + {[],_} -> + pattern(VP, Vt, Old, Bvt0, St0); + {[Var|_],_} -> + %% found variables in key expression + {Vt,Old,add_error(Line,{illegal_map_key_variable,element(1,Var)},St0)} + end; %%pattern({struct,_Line,_Tag,Ps}, Vt, Old, Bvt, St) -> %% pattern_list(Ps, Vt, Old, Bvt, St); pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) -> @@ -1753,6 +1771,14 @@ gexpr({cons,_Line,H,T}, Vt, St) -> gexpr_list([H,T], Vt, St); gexpr({tuple,_Line,Es}, Vt, St) -> gexpr_list(Es, Vt, St); +gexpr({map,_Line,Es}, Vt, St) -> + gexpr_list(Es, Vt, St); +gexpr({map,_Line,Src,Es}, Vt, St) -> + gexpr_list([Src|Es], Vt, St); +gexpr({map_field_assoc,_Line,K,V}, Vt, St) -> + gexpr_list([K,V], Vt, St); +gexpr({map_field_exact,_Line,K,V}, Vt, St) -> + gexpr_list([K,V], Vt, St); gexpr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end ); @@ -1970,6 +1996,24 @@ expr({bc,_Line,E,Qs}, Vt, St) -> handle_comprehension(E, Qs, Vt, St); expr({tuple,_Line,Es}, Vt, St) -> expr_list(Es, Vt, St); +expr({map,Line,Es}, Vt, St) -> + {Rvt,St1} = expr_list(Es,Vt,St), + case is_valid_map_construction(Es) of + true -> {Rvt,St1}; + false -> {[],add_error(Line,illegal_map_construction,St1)} + end; +expr({map,_Line,Src,Es}, Vt, St) -> + expr_list([Src|Es], Vt, St); +expr({map_field_assoc,Line,K,V}, Vt, St) -> + case is_valid_map_key(K,St) of + true -> expr_list([K,V], Vt, St); + {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)} + end; +expr({map_field_exact,Line,K,V}, Vt, St) -> + case is_valid_map_key(K,St) of + true -> expr_list([K,V], Vt, St); + {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)} + end; expr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end); @@ -2229,6 +2273,20 @@ is_valid_call(Call) -> _ -> true end. +%% check_map_construction +%% Only #{ K => V }, i.e. assoc is a valid construction +is_valid_map_construction([{map_field_assoc,_,_,_}|Es]) -> + is_valid_map_construction(Es); +is_valid_map_construction([]) -> true; +is_valid_map_construction(_) -> false. + +is_valid_map_key(K,St) -> + case expr(K,[],St) of + {[],_} -> true; + {[Var|_],_} -> + {false,element(1,Var)} + end. + %% record_def(Line, RecordName, [RecField], State) -> State. %% Add a record definition if it does not already exist. Normalise %% so that all fields have explicit initial value. @@ -2549,6 +2607,13 @@ check_type({type, L, range, [From, To]}, SeenVars, St) -> _ -> add_error(L, {type_syntax, range}, St) end, {SeenVars, St1}; +check_type({type, _L, map, any}, SeenVars, St) -> {SeenVars, St}; +check_type({type, _L, map, Pairs}, SeenVars, St) -> + lists:foldl(fun(Pair, {AccSeenVars, AccSt}) -> + check_type(Pair, AccSeenVars, AccSt) + end, {SeenVars, St}, Pairs); +check_type({type, _L, map_field_assoc, Dom, Range}, SeenVars, St) -> + check_type({type, -1, product, [Dom, Range]}, SeenVars, St); check_type({type, _L, tuple, any}, SeenVars, St) -> {SeenVars, St}; check_type({type, _L, any}, SeenVars, St) -> {SeenVars, St}; check_type({type, L, binary, [Base, Unit]}, SeenVars, St) -> @@ -2654,6 +2719,7 @@ is_default_type({iodata, 0}) -> true; is_default_type({iolist, 0}) -> true; is_default_type({list, 0}) -> true; is_default_type({list, 1}) -> true; +is_default_type({map, 0}) -> true; is_default_type({maybe_improper_list, 0}) -> true; is_default_type({maybe_improper_list, 2}) -> true; is_default_type({mfa, 0}) -> true; |