Skip to content

Commit

Permalink
Fix partial record matching in map generator
Browse files Browse the repository at this point in the history
When attempting to match part of a record in the key of a map
generator, the entire record would be matched.

Example:

    -module(t).
    -export([test/0]).
    -record(r, {a,b}).

    f(Map) ->
        [V || #r{a=N} := V <- Map, is_integer(N)].

    test() ->
        f(#{#r{a=1} => 1, #r{a=2,b=42} => 2}).

It would be expected that `t:test()` would return `[1,2]`, but it
returned `[1]` because the entire record was matched, instead of just
field `a`. Therefore, only the first record `#r{a=1,b=undefined}`
would match.

Fixes #7875
  • Loading branch information
bjorng committed Nov 17, 2023
1 parent c41d424 commit 3de9ae0
Showing 2 changed files with 22 additions and 3 deletions.
16 changes: 16 additions & 0 deletions lib/compiler/test/mc_SUITE.erl
Original file line number Diff line number Diff line change
@@ -55,6 +55,8 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

-record(foo, {a,b}).

basic(_Config) ->
mc_double(0),
mc_double(1),
@@ -106,6 +108,20 @@ basic(_Config) ->
<<>> = << <<0>> || a := b <- #{x => y} >>,
<<0>> = << <<0>> || a := b <- #{a => b} >>,

%% Matching partial records.
RecordMap = id(#{#foo{a=I,b=I*I} => I*I*I || I <- [1,2,3,4]}),

EvenMap = maps:from_list([{K,V} ||
{#foo{a=N}=K,V} <- maps:to_list(RecordMap),
N rem 2 =:= 0]),
EvenMap = #{K => V ||
#foo{a=N}=K := V <- RecordMap,
N rem 2 =:= 0},

Odd = lists:sort([V || {#foo{a=N}, V} <- maps:to_list(RecordMap),
N rem 2 =:= 1]),
Odd = lists:sort([V || #foo{a=N} := V <- RecordMap, N rem 2 =:= 1]),

ok.

mc_double(Size) ->
9 changes: 6 additions & 3 deletions lib/stdlib/src/erl_expand_records.erl
Original file line number Diff line number Diff line change
@@ -526,9 +526,12 @@ lc_tq(Anno, [{b_generate,AnnoG,P0,G0} | Qs0], St0) ->
{[{b_generate,AnnoG,P1,G1} | Qs1],St3};
lc_tq(Anno, [{m_generate,AnnoG,P0,G0} | Qs0], St0) ->
{G1,St1} = expr(G0, St0),
{P1,St2} = pattern(P0, St1),
{Qs1,St3} = lc_tq(Anno, Qs0, St2),
{[{m_generate,AnnoG,P1,G1} | Qs1],St3};
{map_field_exact,AnnoMFE,KeyP0,ValP0} = P0,
{KeyP1,St2} = pattern(KeyP0, St1),
{ValP1,St3} = pattern(ValP0, St2),
{Qs1,St4} = lc_tq(Anno, Qs0, St3),
P1 = {map_field_exact,AnnoMFE,KeyP1,ValP1},
{[{m_generate,AnnoG,P1,G1} | Qs1],St4};
lc_tq(Anno, [F0 | Qs0], #exprec{calltype=Calltype,raw_records=Records}=St0) ->
%% Allow record/2 and expand out as guard test.
IsOverriden = fun(FA) ->

0 comments on commit 3de9ae0

Please sign in to comment.