Skip to content

Commit

Permalink
debugger: Fix incorrect evaluation of nested records in guard
Browse files Browse the repository at this point in the history
Closes #8120
  • Loading branch information
bjorng committed Mar 19, 2024
1 parent 0418c10 commit 640339f
Show file tree
Hide file tree
Showing 2 changed files with 44 additions and 2 deletions.
17 changes: 17 additions & 0 deletions lib/debugger/src/dbg_ieval.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1463,6 +1463,9 @@ guard_expr({'orelse',_,E1,E2}, Bs) ->
{value,_Val}=Res -> Res
end
end;
guard_expr({'case',_,E0,Cs}, Bs) ->
{value,E} = guard_expr(E0, Bs),
guard_case_clauses(E, Cs, Bs);
guard_expr({dbg,_,self,[]}, _) ->
{value,get(self)};
guard_expr({safe_bif,_,erlang,'not',As0}, Bs) ->
Expand Down Expand Up @@ -1505,6 +1508,20 @@ guard_expr({bin,_,Flds}, Bs) ->
end),
{value,V}.

%% guard_case_clauses(Value, Clauses, Bindings, Error, Ieval)
%% Error = try_clause | case_clause
guard_case_clauses(Val, [{clause,_,[P],G,B}|Cs], Bs0) ->
case match(P, Val, Bs0) of
{match,Bs} ->
case guard(G, Bs) of
true ->
guard_expr(hd(B), Bs);
false ->
guard_case_clauses(Val, Cs, Bs0)
end;
nomatch ->
guard_case_clauses(Val, Cs, Bs0)
end.

%% eval_map_fields([Field], Bindings, IEvalState) ->
%% {[{map_assoc | map_exact,Key,Value}],Bindings}
Expand Down
29 changes: 27 additions & 2 deletions lib/debugger/test/record_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,8 @@
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2,
init_per_testcase/2,end_per_testcase/2,
init_per_suite/1,end_per_suite/1,
errors/1,record_test/1,eval_once/1]).
errors/1,record_test/1,eval_once/1,
nested_in_guard/1]).

-export([debug/0]).

Expand All @@ -50,7 +51,7 @@ end_per_group(_GroupName, Config) ->


cases() ->
[errors, record_test, eval_once].
[errors, record_test, eval_once, nested_in_guard].

init_per_testcase(_Case, Config) ->
test_lib:interpret(?MODULE),
Expand Down Expand Up @@ -295,6 +296,30 @@ once(Test, Record) ->
end,
Result.

nested_in_guard(_Config) ->
B = #bar{d = []},
F = #foo{a = B},

ok = do_nested_in_guard(#foo{a=#bar{d=[]}}),
not_ok = do_nested_in_guard(#foo{a=#bar{}}),
not_ok = do_nested_in_guard(#foo{a={no_bar,a,b,c,d}}),
not_ok = do_nested_in_guard(#foo{a={bar,a}}),
not_ok = do_nested_in_guard(42),
not_ok = do_nested_in_guard(#bar{}),
not_ok = do_nested_in_guard([]),

ok.

-define(is_foo(X), (((X#foo.a)#bar.d == []))).

do_nested_in_guard(F) ->
if
?is_foo(F) ->
ok;
true ->
not_ok
end.

id(I) ->
I.

Expand Down

0 comments on commit 640339f

Please sign in to comment.