Skip to content

Commit 3de9ae0

Browse files
committed
Fix partial record matching in map generator
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
1 parent c41d424 commit 3de9ae0

File tree

2 files changed

+22
-3
lines changed

2 files changed

+22
-3
lines changed

lib/compiler/test/mc_SUITE.erl

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,8 @@ init_per_group(_GroupName, Config) ->
5555
end_per_group(_GroupName, Config) ->
5656
Config.
5757

58+
-record(foo, {a,b}).
59+
5860
basic(_Config) ->
5961
mc_double(0),
6062
mc_double(1),
@@ -106,6 +108,20 @@ basic(_Config) ->
106108
<<>> = << <<0>> || a := b <- #{x => y} >>,
107109
<<0>> = << <<0>> || a := b <- #{a => b} >>,
108110

111+
%% Matching partial records.
112+
RecordMap = id(#{#foo{a=I,b=I*I} => I*I*I || I <- [1,2,3,4]}),
113+
114+
EvenMap = maps:from_list([{K,V} ||
115+
{#foo{a=N}=K,V} <- maps:to_list(RecordMap),
116+
N rem 2 =:= 0]),
117+
EvenMap = #{K => V ||
118+
#foo{a=N}=K := V <- RecordMap,
119+
N rem 2 =:= 0},
120+
121+
Odd = lists:sort([V || {#foo{a=N}, V} <- maps:to_list(RecordMap),
122+
N rem 2 =:= 1]),
123+
Odd = lists:sort([V || #foo{a=N} := V <- RecordMap, N rem 2 =:= 1]),
124+
109125
ok.
110126

111127
mc_double(Size) ->

lib/stdlib/src/erl_expand_records.erl

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -526,9 +526,12 @@ lc_tq(Anno, [{b_generate,AnnoG,P0,G0} | Qs0], St0) ->
526526
{[{b_generate,AnnoG,P1,G1} | Qs1],St3};
527527
lc_tq(Anno, [{m_generate,AnnoG,P0,G0} | Qs0], St0) ->
528528
{G1,St1} = expr(G0, St0),
529-
{P1,St2} = pattern(P0, St1),
530-
{Qs1,St3} = lc_tq(Anno, Qs0, St2),
531-
{[{m_generate,AnnoG,P1,G1} | Qs1],St3};
529+
{map_field_exact,AnnoMFE,KeyP0,ValP0} = P0,
530+
{KeyP1,St2} = pattern(KeyP0, St1),
531+
{ValP1,St3} = pattern(ValP0, St2),
532+
{Qs1,St4} = lc_tq(Anno, Qs0, St3),
533+
P1 = {map_field_exact,AnnoMFE,KeyP1,ValP1},
534+
{[{m_generate,AnnoG,P1,G1} | Qs1],St4};
532535
lc_tq(Anno, [F0 | Qs0], #exprec{calltype=Calltype,raw_records=Records}=St0) ->
533536
%% Allow record/2 and expand out as guard test.
534537
IsOverriden = fun(FA) ->

0 commit comments

Comments
 (0)