Skip to content

Commit

Permalink
stdlib: Deny map keys defined as #{ .. := .. } in patterns
Browse files Browse the repository at this point in the history
  • Loading branch information
psyeugenic committed Apr 3, 2014
1 parent c655521 commit 7b11f5a
Show file tree
Hide file tree
Showing 2 changed files with 33 additions and 17 deletions.
36 changes: 20 additions & 16 deletions lib/stdlib/src/erl_lint.erl
Expand Up @@ -1407,7 +1407,7 @@ pattern({map,_Line,Ps}, Vt, Old, Bvt, St) ->
({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) ->
{Psvt,Bvt0,add_error(L, illegal_pattern, St0)};
({map_field_exact,L,KP,VP}, {Psvt,Bvt0,St0}) ->
case is_valid_map_key(KP, St0) of
case is_valid_map_key(KP, pattern, St0) of
true ->
{Pvt,Bvt1,St1} = pattern(VP, Vt, Old, Bvt, St0),
{vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt0, Bvt1), St1};
Expand Down Expand Up @@ -2322,14 +2322,16 @@ is_valid_call(Call) ->
%% check for value expression without variables

is_valid_map_key(K,St) ->
is_valid_map_key(K,expr,St).
is_valid_map_key(K,Ctx,St) ->
case expr(K,[],St) of
{[],_} ->
is_valid_map_key_value(K);
is_valid_map_key_value(K,Ctx);
{[Var|_],_} ->
{false,variable,element(1,Var)}
end.

is_valid_map_key_value(K) ->
is_valid_map_key_value(K,Ctx) ->
case K of
{char,_,_} -> true;
{integer,_,_} -> true;
Expand All @@ -2338,42 +2340,44 @@ is_valid_map_key_value(K) ->
{nil,_} -> true;
{atom,_,_} -> true;
{cons,_,H,T} ->
is_valid_map_key_value(H) andalso
is_valid_map_key_value(T);
is_valid_map_key_value(H,Ctx) andalso
is_valid_map_key_value(T,Ctx);
{tuple,_,Es} ->
foldl(fun(E,B) ->
B andalso is_valid_map_key_value(E)
B andalso is_valid_map_key_value(E,Ctx)
end,true,Es);
{map,_,Arg,Ps} ->
% only check for value expressions to be valid
% invalid map expressions are later checked in
% core and kernel
is_valid_map_key_value(Arg) andalso foldl(fun
is_valid_map_key_value(Arg,Ctx) andalso foldl(fun
({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
Tag =:= map_field_exact ->
B andalso is_valid_map_key_value(Ke)
andalso is_valid_map_key_value(Ve)
Tag =:= map_field_exact, Ctx =:= expr ->
B andalso is_valid_map_key_value(Ke,Ctx)
andalso is_valid_map_key_value(Ve,Ctx);
(_,_) -> false
end,true,Ps);
{map,_,Ps} ->
foldl(fun
({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
Tag =:= map_field_exact ->
B andalso is_valid_map_key_value(Ke)
andalso is_valid_map_key_value(Ve)
Tag =:= map_field_exact, Ctx =:= expr ->
B andalso is_valid_map_key_value(Ke,Ctx)
andalso is_valid_map_key_value(Ve,Ctx);
(_,_) -> false
end, true, Ps);
{record,_,_,Fs} ->
foldl(fun
({record_field,_,Ke,Ve},B) ->
B andalso is_valid_map_key_value(Ke)
andalso is_valid_map_key_value(Ve)
B andalso is_valid_map_key_value(Ke,Ctx)
andalso is_valid_map_key_value(Ve,Ctx)
end,true,Fs);
{bin,_,Es} ->
% only check for value expressions to be valid
% invalid binary expressions are later checked in
% core and kernel
foldl(fun
({bin_element,_,E,_,_},B) ->
B andalso is_valid_map_key_value(E)
B andalso is_valid_map_key_value(E,Ctx)
end,true,Es);
_ -> false
end.
Expand Down
14 changes: 13 additions & 1 deletion lib/stdlib/test/erl_lint_SUITE.erl
Expand Up @@ -3406,7 +3406,19 @@ maps(Config) ->
{4,erl_lint,illegal_map_key},
{6,erl_lint,illegal_map_key},
{8,erl_lint,illegal_map_key},
{10,erl_lint,illegal_map_key}],[]}}],
{10,erl_lint,illegal_map_key}],[]}},
{errors_in_map_keys_pattern,
<<"t(#{ a := 2,
#{} := A,
#{ 3 => 33 } := hi,
#{ 3 := 33 } := hi,
#{ hi => 54, \"hello\" => 45 } := hi,
#{ V => 33 } := hi }) ->
A.
">>,
[],
{errors,[{4,erl_lint,illegal_map_key},
{6,erl_lint,{illegal_map_key_variable,'V'}}],[]}}],
[] = run(Config, Ts),
ok.

Expand Down

0 comments on commit 7b11f5a

Please sign in to comment.