1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1998-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19
20-module(erl_eval_SUITE).
21-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
22	 init_per_testcase/2, end_per_testcase/2,
23	 init_per_group/2,end_per_group/2]).
24
25-export([guard_1/1, guard_2/1,
26	 match_pattern/1,
27	 match_bin/1,
28	 string_plusplus/1,
29	 pattern_expr/1,
30         guard_3/1, guard_4/1, guard_5/1,
31         lc/1,
32         simple_cases/1,
33         unary_plus/1,
34         apply_atom/1,
35         otp_5269/1,
36         otp_6539/1,
37         otp_6543/1,
38         otp_6787/1,
39         otp_6977/1,
40	 otp_7550/1,
41         otp_8133/1,
42         otp_10622/1,
43         otp_13228/1,
44         otp_14826/1,
45         funs/1,
46	 try_catch/1,
47	 eval_expr_5/1,
48	 zero_width/1,
49         eep37/1,
50         eep43/1,
51         otp_15035/1,
52         otp_16439/1,
53         otp_14708/1,
54         otp_16545/1,
55         otp_16865/1]).
56
57%%
58%% Define to run outside of test server
59%%
60%%-define(STANDALONE,1).
61
62-import(lists,[concat/1, sort/1]).
63
64-export([count_down/2, count_down_fun/0, do_apply/2,
65         local_func/3, local_func_value/2]).
66-export([simple/0]).
67
68-ifdef(STANDALONE).
69-define(config(A,B),config(A,B)).
70-export([config/2]).
71-define(line, noop, ).
72config(priv_dir,_) ->
73    ".".
74-else.
75-include_lib("common_test/include/ct.hrl").
76-endif.
77
78init_per_testcase(_Case, Config) ->
79    Config.
80
81end_per_testcase(_Case, _Config) ->
82    ok.
83
84suite() ->
85    [{ct_hooks,[ts_install_cth]},
86     {timetrap,{minutes,1}}].
87
88all() ->
89    [guard_1, guard_2, match_pattern, string_plusplus,
90     pattern_expr, match_bin, guard_3, guard_4, guard_5, lc,
91     simple_cases, unary_plus, apply_atom, otp_5269,
92     otp_6539, otp_6543, otp_6787, otp_6977, otp_7550,
93     otp_8133, otp_10622, otp_13228, otp_14826,
94     funs, try_catch, eval_expr_5, zero_width,
95     eep37, eep43, otp_15035, otp_16439, otp_14708, otp_16545, otp_16865].
96
97groups() ->
98    [].
99
100init_per_suite(Config) ->
101    Config.
102
103end_per_suite(_Config) ->
104    ok.
105
106init_per_group(_GroupName, Config) ->
107    Config.
108
109end_per_group(_GroupName, Config) ->
110    Config.
111
112%% OTP-2405
113guard_1(Config) when is_list(Config) ->
114    {ok,Tokens ,_} =
115	erl_scan:string("if a+4 == 4 -> yes; true -> no end. "),
116    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
117    no = guard_1_compiled(),
118    {value, no, []} = erl_eval:expr(Expr, []),
119    ok.
120
121guard_1_compiled() ->
122    if a+4 == 4 -> yes; true -> no end.
123
124%% Similar to guard_1, but type-correct.
125guard_2(Config) when is_list(Config) ->
126    {ok,Tokens ,_} =
127	erl_scan:string("if 6+4 == 4 -> yes; true -> no end. "),
128    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
129    no = guard_2_compiled(),
130    {value, no, []} = erl_eval:expr(Expr, []),
131    ok.
132
133guard_2_compiled() ->
134    if 6+4 == 4 -> yes; true -> no end.
135
136%% OTP-3069: syntactic sugar string ++ ...
137string_plusplus(Config) when is_list(Config) ->
138    check(fun() -> case "abc" of "ab" ++ L -> L end end,
139	  "case \"abc\" of \"ab\" ++ L -> L end. ",
140	  "c"),
141    check(fun() -> case "abcde" of "ab" ++ "cd" ++ L -> L end end,
142	  "case \"abcde\" of \"ab\" ++ \"cd\" ++ L -> L end. ",
143	  "e"),
144    check(fun() -> case "abc" of [97, 98] ++ L -> L end end,
145	  "case \"abc\" of [97, 98] ++ L -> L end. ",
146	  "c"),
147    ok.
148
149%% OTP-2983: match operator in pattern.
150match_pattern(Config) when is_list(Config) ->
151    check(fun() -> case {a, b} of {a, _X}=Y -> {x,Y} end end,
152	  "case {a, b} of {a, X}=Y -> {x,Y} end. ",
153	  {x, {a, b}}),
154    check(fun() -> case {a, b} of Y={a, _X} -> {x,Y} end end,
155	  "case {a, b} of Y={a, X} -> {x,Y} end. ",
156	  {x, {a, b}}),
157    check(fun() -> case {a, b} of Y={a, _X}=Z -> {Z,Y} end end,
158	  "case {a, b} of Y={a, X}=Z -> {Z,Y} end. ",
159	  {{a, b}, {a, b}}),
160    check(fun() -> A = 4, B = 28, <<13:(A+(X=B))>>, X end,
161	  "begin A = 4, B = 28, <<13:(A+(X=B))>>, X end.",
162	  28),
163    ok.
164
165%% Binary match problems.
166match_bin(Config) when is_list(Config) ->
167    check(fun() -> <<"abc">> = <<"abc">> end,
168	  "<<\"abc\">> = <<\"abc\">>. ",
169	  <<"abc">>),
170    check(fun() ->
171		  <<Size,B:Size/binary,Rest/binary>> = <<2,"AB","CD">>,
172		  {Size,B,Rest}
173	  end,
174	  "begin <<Size,B:Size/binary,Rest/binary>> = <<2,\"AB\",\"CD\">>, "
175	  "{Size,B,Rest} end. ",
176	  {2,<<"AB">>,<<"CD">>}),
177    ok.
178
179%% OTP-3144: compile-time expressions in pattern.
180pattern_expr(Config) when is_list(Config) ->
181    check(fun() -> case 4 of 2+2 -> ok end end,
182	  "case 4 of 2+2 -> ok end. ",
183	  ok),
184    check(fun() -> case 2 of +2 -> ok end end,
185	  "case 2 of +2 -> ok end. ",
186	  ok),
187    ok.
188
189%% OTP-4518.
190guard_3(Config) when is_list(Config) ->
191    check(fun() -> if false -> false; true -> true end end,
192	  "if false -> false; true -> true end.",
193	  true),
194    check(fun() -> if <<"hej">> == <<"hopp">> -> true;
195		      true -> false end end,
196	  "begin if <<\"hej\">> == <<\"hopp\">> -> true;
197                          true -> false end end.",
198                false),
199    check(fun() -> if <<"hej">> == <<"hej">> -> true;
200		      true -> false end end,
201	  "begin if <<\"hej\">> == <<\"hej\">> -> true;
202                          true -> false end end.",
203                true),
204    ok.
205
206%% OTP-4885.
207guard_4(Config) when is_list(Config) ->
208    check(fun() -> if erlang:'+'(3,a) -> true ; true -> false end end,
209	  "if erlang:'+'(3,a) -> true ; true -> false end.",
210	  false),
211    check(fun() -> if erlang:is_integer(3) -> true ; true -> false end
212	  end,
213	  "if erlang:is_integer(3) -> true ; true -> false end.",
214	  true),
215    check(fun() -> [X || X <- [1,2,3], erlang:is_integer(X)] end,
216	  "[X || X <- [1,2,3], erlang:is_integer(X)].",
217	  [1,2,3]),
218    check(fun() -> if is_atom(is_integer(a)) -> true ; true -> false end
219	  end,
220	  "if is_atom(is_integer(a)) -> true ; true -> false end.",
221	  true),
222    check(fun() -> if erlang:is_atom(erlang:is_integer(a)) -> true;
223		      true -> false end end,
224	  "if erlang:is_atom(erlang:is_integer(a)) -> true; "
225	  "true -> false end.",
226	  true),
227    check(fun() -> if is_atom(3+a) -> true ; true -> false end end,
228	  "if is_atom(3+a) -> true ; true -> false end.",
229	  false),
230    check(fun() -> if erlang:is_atom(3+a) -> true ; true -> false end
231	  end,
232	  "if erlang:is_atom(3+a) -> true ; true -> false end.",
233	  false),
234    ok.
235
236%% Guards with erlang:'=='/2.
237guard_5(Config) when is_list(Config) ->
238    {ok,Tokens ,_} =
239	erl_scan:string("case 1 of A when erlang:'=='(A, 1) -> true end."),
240    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
241    true = guard_5_compiled(),
242    {value, true, [{'A',1}]} = erl_eval:expr(Expr, []),
243    ok.
244
245guard_5_compiled() ->
246    case 1 of A when erlang:'=='(A, 1) -> true end.
247
248%% OTP-4518.
249lc(Config) when is_list(Config) ->
250    check(fun() -> X = 32, [X || X <- [1,2,3]] end,
251	  "begin X = 32, [X || X <- [1,2,3]] end.",
252	  [1,2,3]),
253    check(fun() -> X = 32,
254		   [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end,
255	  %% "binsize variable"          ^
256	  "begin X = 32,
257                 [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end.",
258                [1,2]),
259    check(fun() -> Y = 13,[X || {X,Y} <- [{1,2}]] end,
260	  "begin Y = 13,[X || {X,Y} <- [{1,2}]] end.",
261	  [1]),
262    error_check("begin [A || X <- [{1,2}], 1 == A] end.",
263		{unbound_var,'A'}),
264    error_check("begin X = 32,
265                        [{Y,W} || X <- [1,2,32,Y=4], Z <- [1,2,W=3]] end.",
266                      {unbound_var,'Y'}),
267    error_check("begin X = 32,<<A:B>> = <<100:X>> end.",
268		{unbound_var,'B'}),
269    check(fun() -> [X || X <- [1,2,3,4], not (X < 2)] end,
270	  "begin [X || X <- [1,2,3,4], not (X < 2)] end.",
271	  [2,3,4]),
272    check(fun() -> [X || X <- [true,false], X] end,
273	  "[X || X <- [true,false], X].", [true]),
274    ok.
275
276%% Simple cases, just to cover some code.
277simple_cases(Config) when is_list(Config) ->
278    check(fun() -> A = $C end, "A = $C.", $C),
279    %% check(fun() -> A = 3.14 end, "A = 3.14.", 3.14),
280    check(fun() -> self() ! a, A = receive a -> true end end,
281	  "begin self() ! a, A = receive a -> true end end.",
282	  true),
283    check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
284		   receive b -> b end,
285		   {messages, [a,c]} =
286		       erlang:process_info(self(), messages),
287		   c:flush() end,
288	  "begin c:flush(), self() ! a, self() ! b, self() ! c,"
289	  "receive b -> b end,"
290	  "{messages, [a,c]} ="
291	  "     erlang:process_info(self(), messages), c:flush() end.",
292	  ok),
293    check(fun() -> self() ! a, A = receive a -> true
294				   after 0 -> false end end,
295	  "begin self() ! a, A = receive a -> true"
296	  "                      after 0 -> false end end.",
297	  true),
298    check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
299		   receive b -> b after 0 -> true end,
300		   {messages, [a,c]} =
301		       erlang:process_info(self(), messages),
302		   c:flush() end,
303	  "begin c:flush(), self() ! a, self() ! b, self() ! c,"
304	  "receive b -> b after 0 -> true end,"
305	  "{messages, [a,c]} ="
306	  "     erlang:process_info(self(), messages), c:flush() end.",
307	  ok),
308    check(fun() -> receive _ -> true after 10 -> false end end,
309	  "receive _ -> true after 10 -> false end.",
310	  false),
311    check(fun() -> F = fun(A) -> A end, true = 3 == F(3) end,
312	  "begin F = fun(A) -> A end, true = 3 == F(3) end.",
313	  true),
314    check(fun() -> F = fun(A) -> A end, true = 3 == apply(F, [3]) end,
315	  "begin F = fun(A) -> A end, true = 3 == apply(F,[3]) end.",
316	  true),
317    check(fun() -> catch throw(a) end, "catch throw(a).", a),
318    check(fun() -> catch a end, "catch a.", a),
319    check(fun() -> 4 == 3 end, "4 == 3.", false),
320    check(fun() -> not true end, "not true.", false),
321    check(fun() -> -3 end, "-3.", -3),
322
323    error_check("3.0 = 4.0.", {badmatch,4.0}),
324    check(fun() -> <<(3.0+2.0):32/float>> = <<5.0:32/float>> end,
325	  "<<(3.0+2.0):32/float>> = <<5.0:32/float>>.",
326	  <<5.0:32/float>>),
327
328    check(fun() -> false andalso kludd end, "false andalso kludd.",
329	  false),
330    check(fun() -> true andalso true end, "true andalso true.",
331	  true),
332    check(fun() -> true andalso false end, "true andalso false.",
333	  false),
334    check(fun() -> true andalso kludd end, "true andalso kludd.",
335	  kludd),
336    error_check("kladd andalso kludd.", {badarg,kladd}),
337
338    check(fun() -> if false andalso kludd -> a; true -> b end end,
339	  "if false andalso kludd -> a; true -> b end.",
340	  b),
341    check(fun() -> if true andalso true -> a; true -> b end end,
342	  "if true andalso true -> a; true -> b end.",
343	  a),
344    check(fun() -> if true andalso false -> a; true -> b end end,
345	  "if true andalso false -> a; true -> b end.",
346	  b),
347
348    check(fun() -> true orelse kludd end,
349	  "true orelse kludd.", true),
350    check(fun() -> false orelse false end,
351	  "false orelse false.", false),
352    check(fun() -> false orelse true end,
353	  "false orelse true.", true),
354    check(fun() -> false orelse kludd end,
355	  "false orelse kludd.", kludd),
356    error_check("kladd orelse kludd.", {badarg,kladd}),
357    error_check("[X || X <- [1,2,3], begin 1 end].",{bad_filter,1}),
358    error_check("[X || X <- a].",{bad_generator,a}),
359
360    check(fun() -> if true orelse kludd -> a; true -> b end end,
361	  "if true orelse kludd -> a; true -> b end.", a),
362    check(fun() -> if false orelse false -> a; true -> b end end,
363	  "if false orelse false -> a; true -> b end.", b),
364    check(fun() -> if false orelse true -> a; true -> b end end,
365	  "if false orelse true -> a; true -> b end.", a),
366
367    check(fun() -> [X || X <- [1,2,3], X+2] end,
368	  "[X || X <- [1,2,3], X+2].", []),
369
370    check(fun() -> [X || X <- [1,2,3], [X] == [X || X <- [2]]] end,
371	  "[X || X <- [1,2,3], [X] == [X || X <- [2]]].",
372	  [2]),
373    check(fun() -> F = fun(1) -> ett; (2) -> zwei end,
374		   ett = F(1), zwei = F(2) end,
375	  "begin F = fun(1) -> ett; (2) -> zwei end,
376                         ett = F(1), zwei = F(2) end.",
377                zwei),
378    check(fun() -> F = fun(X) when X == 1 -> ett;
379			  (X) when X == 2 -> zwei end,
380		   ett = F(1), zwei = F(2) end,
381	  "begin F = fun(X) when X == 1 -> ett;
382                              (X) when X == 2 -> zwei end,
383	  ett = F(1), zwei = F(2) end.",
384                zwei),
385    error_check("begin F = fun(1) -> ett end, zwei = F(2) end.",
386		function_clause),
387    check(fun() -> if length([1]) == 1 -> yes;
388		      true -> no end end,
389	  "if length([1]) == 1 -> yes;
390                            true -> no end.",
391                yes),
392    check(fun() -> if is_integer(3) -> true; true -> false end end,
393	  "if is_integer(3) -> true; true -> false end.", true),
394    check(fun() -> if integer(3) -> true; true -> false end end,
395	  "if integer(3) -> true; true -> false end.", true),
396    check(fun() -> if is_float(3) -> true; true -> false end end,
397	  "if is_float(3) -> true; true -> false end.", false),
398    check(fun() -> if float(3) -> true; true -> false end end,
399	  "if float(3) -> true; true -> false end.", false),
400    check(fun() -> if is_number(3) -> true; true -> false end end,
401	  "if is_number(3) -> true; true -> false end.", true),
402    check(fun() -> if number(3) -> true; true -> false end end,
403	  "if number(3) -> true; true -> false end.", true),
404    check(fun() -> if is_atom(a) -> true; true -> false end end,
405	  "if is_atom(a) -> true; true -> false end.", true),
406    check(fun() -> if atom(a) -> true; true -> false end end,
407	  "if atom(a) -> true; true -> false end.", true),
408    check(fun() -> if is_list([]) -> true; true -> false end end,
409	  "if is_list([]) -> true; true -> false end.", true),
410    check(fun() -> if list([]) -> true; true -> false end end,
411	  "if list([]) -> true; true -> false end.", true),
412    check(fun() -> if is_tuple({}) -> true; true -> false end end,
413	  "if is_tuple({}) -> true; true -> false end.", true),
414    check(fun() -> if tuple({}) -> true; true -> false end end,
415	  "if tuple({}) -> true; true -> false end.", true),
416    check(fun() -> if is_pid(self()) -> true; true -> false end end,
417	  "if is_pid(self()) -> true; true -> false end.", true),
418    check(fun() -> if pid(self()) -> true; true -> false end end,
419	  "if pid(self()) -> true; true -> false end.", true),
420    check(fun() -> R = make_ref(), if is_reference(R) -> true;
421				      true -> false end end,
422	  "begin R = make_ref(), if is_reference(R) -> true;"
423	  "true -> false end end.", true),
424    check(fun() -> R = make_ref(), if reference(R) -> true;
425				      true -> false end end,
426	  "begin R = make_ref(), if reference(R) -> true;"
427	  "true -> false end end.", true),
428    check(fun() -> if is_port(a) -> true; true -> false end end,
429	  "if is_port(a) -> true; true -> false end.", false),
430    check(fun() -> if port(a) -> true; true -> false end end,
431	  "if port(a) -> true; true -> false end.", false),
432    check(fun() -> if is_function(a) -> true; true -> false end end,
433	  "if is_function(a) -> true; true -> false end.", false),
434    check(fun() -> if function(a) -> true; true -> false end end,
435	  "if function(a) -> true; true -> false end.", false),
436    check(fun() -> if is_binary(<<>>) -> true; true -> false end end,
437	  "if is_binary(<<>>) -> true; true -> false end.", true),
438    check(fun() -> if binary(<<>>) -> true; true -> false end end,
439	  "if binary(<<>>) -> true; true -> false end.", true),
440    check(fun() -> if is_integer(a) == true -> yes;
441		      true -> no end end,
442	  "if is_integer(a) == true -> yes;
443                            true -> no end.",
444                no),
445    check(fun() -> if [] -> true; true -> false end end,
446	  "if [] -> true; true -> false end.", false),
447    error_check("if lists:member(1,[1]) -> true; true -> false end.",
448		illegal_guard_expr),
449    error_check("if false -> true end.", if_clause),
450    check(fun() -> if a+b -> true; true -> false end end,
451	  "if a + b -> true; true -> false end.", false),
452    check(fun() -> if + b -> true; true -> false end end,
453	  "if + b -> true; true -> false end.", false),
454    error_check("case foo of bar -> true end.", {case_clause,foo}),
455    error_check("case 4 of 2+a -> true; _ -> false end.",
456		illegal_pattern),
457    error_check("case 4 of +a -> true; _ -> false end.",
458		illegal_pattern),
459    check(fun() -> case a of
460		       X when X == b -> one;
461		       X when X == a -> two
462		   end end,
463	  "begin case a of
464                             X when X == b -> one;
465	      X when X == a -> two
466	 end end.", two),
467    error_check("3 = 4.", {badmatch,4}),
468	  error_check("a = 3.", {badmatch,3}),
469    %% error_check("3.1 = 2.7.",{badmatch,2.7}),
470	  error_check("$c = 4.", {badmatch,4}),
471	  check(fun() -> $c = $c end, "$c = $c.", $c),
472	  check(fun() -> _ = bar end, "_ = bar.", bar),
473	  check(fun() -> A = 14, A = 14 end,
474                "begin A = 14, A = 14 end.", 14),
475	  error_check("begin A = 14, A = 16 end.", {badmatch,16}),
476	  error_check("\"hej\" = \"san\".", {badmatch,"san"}),
477	  check(fun() -> "hej" = "hej" end,
478                "\"hej\" = \"hej\".", "hej"),
479	  error_check("[] = [a].", {badmatch,[a]}),
480	  check(fun() -> [] = [] end, "[] = [].", []),
481	  error_check("[a] = [].", {badmatch,[]}),
482	  error_check("{a,b} = 34.", {badmatch,34}),
483	  check(fun() -> <<X:7>> = <<8:7>>, X end,
484		"begin <<X:7>> = <<8:7>>, X end.", 8),
485	  error_check("<<34:32>> = \"hej\".", {badmatch,"hej"}),
486	  check(fun() -> trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end,
487                "begin trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end.", 0),
488	  check(fun() -> (2#101 band 2#10101) bor (2#110 bxor 2#010) end,
489                "(2#101 band 2#10101) bor (2#110 bxor 2#010).", 5),
490	  check(fun() -> (2#1 bsl 4) + (2#10000 bsr 3) end,
491                "(2#1 bsl 4) + (2#10000 bsr 3).", 18),
492	  check(fun() -> ((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2) end,
493                "((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2).", false),
494	  check(fun() -> (a /= b) or (2 > 4) or (3 >= 3) end,
495                "(a /= b) or (2 > 4) or (3 >= 3).", true),
496	  check(fun() -> "hej" ++ "san" =/= "hejsan" -- "san" end,
497                "\"hej\" ++ \"san\" =/= \"hejsan\" -- \"san\".", true),
498	  check(fun() -> (bnot 1) < -0 end, "(bnot (+1)) < -0.", true),
499	  ok.
500
501%% OTP-4929. Unary plus rejects non-numbers.
502unary_plus(Config) when is_list(Config) ->
503    check(fun() -> F = fun(X) -> + X end,
504		   true = -1 == F(-1) end,
505	  "begin F = fun(X) -> + X end,"
506	  "      true = -1 == F(-1) end.", true, ['F'], none, none),
507    error_check("+a.", badarith),
508    ok.
509
510%% OTP-5064. Can no longer apply atoms.
511apply_atom(Config) when is_list(Config) ->
512    error_check("[X || X <- [[1],[2]],
513                             begin L = length, L(X) =:= 1 end].",
514                      {badfun,length}),
515    ok.
516
517%% OTP-5269. Bugs in the bit syntax.
518otp_5269(Config) when is_list(Config) ->
519    check(fun() -> L = 8,
520                         F = fun(<<A:L,B:A>>) -> B end,
521                         F(<<16:8, 7:16>>)
522                end,
523                "begin
524                   L = 8, F = fun(<<A:L,B:A>>) -> B end, F(<<16:8, 7:16>>)
525                 end.",
526                7),
527    check(fun() -> L = 8,
528                         F = fun(<<L:L,B:L>>) -> B end,
529                         F(<<16:8, 7:16>>)
530                end,
531                "begin
532                   L = 8, F = fun(<<L:L,B:L>>) -> B end, F(<<16:8, 7:16>>)
533                 end.",
534                7),
535    check(fun() -> L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end,
536                "begin L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end.",
537                7),
538    error_check("begin L = 8, <<L:L,B:L>> = <<16:8, 7:16>> end.",
539                      {badmatch,<<16:8,7:16>>}),
540
541    error_check("begin <<L:16,L:L>> = <<16:16,8:16>>, L end.",
542                      {badmatch, <<16:16,8:16>>}),
543    check(fun() -> U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end,
544                "begin U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end.",
545                32),
546    check(fun() -> U = 8, [U || <<U:U>> <- [<<32:8>>]] end,
547                "begin U = 8, [U || <<U:U>> <- [<<32:8>>]] end.",
548                [32]),
549    error_check("(fun({3,<<A:32,A:32>>}) -> a end)
550                          ({3,<<17:32,19:32>>}).",
551                      function_clause),
552    check(fun() -> [X || <<A:8,
553                                 B:A>> <- [<<16:8,19:16>>],
554                               <<X:8>> <- [<<B:8>>]] end,
555                "[X || <<A:8,
556                                 B:A>> <- [<<16:8,19:16>>],
557                               <<X:8>> <- [<<B:8>>]].",
558                [19]),
559    check(fun() ->
560		(fun (<<A:1/binary, B:8/integer, _C:B/binary>>) ->
561			    case A of
562				B -> wrong;
563				_ -> ok
564			    end
565		 end)(<<1,2,3,4>>) end,
566		"(fun(<<A:1/binary, B:8/integer, _C:B/binary>>) ->"
567			    " case A of B -> wrong; _ -> ok end"
568		" end)(<<1, 2, 3, 4>>).",
569		ok),
570    ok.
571
572%% OTP-6539. try/catch bugs.
573otp_6539(Config) when is_list(Config) ->
574    check(fun() ->
575                        F = fun(A,B) ->
576                                    try A+B
577                                    catch _:_ -> dontthinkso
578                                    end
579                            end,
580                        lists:zipwith(F, [1,2], [2,3])
581                end,
582                "begin
583                     F = fun(A,B) ->
584                                 try A+B
585                                 catch _:_ -> dontthinkso
586                                 end
587                         end,
588                     lists:zipwith(F, [1,2], [2,3])
589                 end.",
590                [3, 5]),
591    ok.
592
593%% OTP-6543. bitlevel binaries.
594otp_6543(Config) when is_list(Config) ->
595    check(fun() ->
596                        << <<X>> || <<X>> <- [1,2,3] >>
597                end,
598                "<< <<X>> || <<X>> <- [1,2,3] >>.",
599                <<>>),
600    check(fun() ->
601                        << <<X>> || X <- [1,2,3] >>
602                end,
603                "<< <<X>> || X <- [1,2,3] >>.",
604                <<1,2,3>>),
605    check(fun() ->
606                        << <<X:8>> || <<X:2>> <= <<"hej">> >>
607                end,
608                "<< <<X:8>> || <<X:2>> <= <<\"hej\">> >>.",
609                <<1,2,2,0,1,2,1,1,1,2,2,2>>),
610    check(fun() ->
611                        << <<X:8>> ||
612                            <<65,X:4>> <= <<65,7:4,65,3:4,66,8:4>> >>
613                end,
614                "<< <<X:8>> ||
615                            <<65,X:4>> <= <<65,7:4,65,3:4,66,8:4>> >>.",
616                <<7,3>>),
617    check(fun() -> <<34:18/big>> end,
618                "<<34:18/big>>.",
619                <<0,8,2:2>>),
620    check(fun() -> <<34:18/big-unit:2>> end,
621                "<<34:18/big-unit:2>>.",
622                <<0,0,0,2,2:4>>),
623    check(fun() -> <<34:18/little>> end,
624                "<<34:18/little>>.",
625                <<34,0,0:2>>),
626    case eval_string("<<34:18/native>>.") of
627              <<0,8,2:2>> -> ok;
628              <<34,0,0:2>> -> ok
629          end,
630    check(fun() -> <<34:18/big-signed>> end,
631                "<<34:18/big-signed>>.",
632                <<0,8,2:2>>),
633    check(fun() -> <<34:18/little-signed>> end,
634                "<<34:18/little-signed>>.",
635                <<34,0,0:2>>),
636    case eval_string("<<34:18/native-signed>>.") of
637              <<0,8,2:2>> -> ok;
638              <<34,0,0:2>> -> ok
639          end,
640    check(fun() -> <<34:18/big-unsigned>> end,
641                "<<34:18/big-unsigned>>.",
642                <<0,8,2:2>>),
643    check(fun() -> <<34:18/little-unsigned>> end,
644                "<<34:18/little-unsigned>>.",
645                <<34,0,0:2>>),
646    case eval_string("<<34:18/native-unsigned>>.") of
647              <<0,8,2:2>> -> ok;
648              <<34,0,0:2>> -> ok
649          end,
650    check(fun() -> <<3.14:32/float-big>> end,
651                "<<3.14:32/float-big>>.",
652                <<64,72,245,195>>),
653    check(fun() -> <<3.14:32/float-little>> end,
654                "<<3.14:32/float-little>>.",
655                <<195,245,72,64>>),
656    case eval_string("<<3.14:32/float-native>>.") of
657              <<64,72,245,195>> -> ok;
658              <<195,245,72,64>> -> ok
659          end,
660    error_check("<<(<<17,3:2>>)/binary>>.", badarg),
661    check(fun() -> <<(<<17,3:2>>)/bitstring>> end,
662                "<<(<<17,3:2>>)/bitstring>>.",
663                <<17,3:2>>),
664    check(fun() -> <<(<<17,3:2>>):10/bitstring>> end,
665                "<<(<<17,3:2>>):10/bitstring>>.",
666                <<17,3:2>>),
667    check(fun() -> <<<<344:17>>/binary-unit:17>> end,
668		"<<<<344:17>>/binary-unit:17>>.",
669		<<344:17>>),
670
671    check(fun() -> <<X:18/big>> = <<34:18/big>>, X end,
672                "begin <<X:18/big>> = <<34:18/big>>, X end.",
673                34),
674    check(fun() -> <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end,
675                "begin <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end.",
676                34),
677    check(fun() -> <<X:18/little>> = <<34:18/little>>, X end,
678                "begin <<X:18/little>> = <<34:18/little>>, X end.",
679                34),
680    check(fun() -> <<X:18/native>> = <<34:18/native>>, X end,
681                "begin <<X:18/native>> = <<34:18/native>>, X end.",
682                34),
683    check(fun() -> <<X:18/big-signed>> = <<34:18/big-signed>>, X end,
684                "begin <<X:18/big-signed>> = <<34:18/big-signed>>, X end.",
685                34),
686    check(fun() -> <<X:18/little-signed>> = <<34:18/little-signed>>,
687                         X end,
688                "begin <<X:18/little-signed>> = <<34:18/little-signed>>,
689                       X end.",
690                34),
691    check(fun() -> <<X:18/native-signed>> = <<34:18/native-signed>>,
692                         X end,
693                "begin <<X:18/native-signed>> = <<34:18/native-signed>>,
694                       X end.",
695                34),
696    check(fun() -> <<X:18/big-unsigned>> = <<34:18/big-unsigned>>,
697                         X end,
698                "begin <<X:18/big-unsigned>> = <<34:18/big-unsigned>>,
699                       X end.",
700                34),
701    check(fun() ->
702                        <<X:18/little-unsigned>> = <<34:18/little-unsigned>>,
703                        X end,
704                "begin <<X:18/little-unsigned>> = <<34:18/little-unsigned>>,
705                       X end.",
706                34),
707    check(fun() ->
708                        <<X:18/native-unsigned>> = <<34:18/native-unsigned>>,
709                        X end,
710                "begin <<X:18/native-unsigned>> = <<34:18/native-unsigned>>,
711                       X end.",
712                34),
713    check(fun() -> <<X:32/float-big>> = <<2.0:32/float-big>>, X end,
714                "begin <<X:32/float-big>> = <<2.0:32/float-big>>,
715                        X end.",
716                2.0),
717    check(fun() -> <<X:32/float-little>> = <<2.0:32/float-little>>,
718                         X end,
719                "begin <<X:32/float-little>> = <<2.0:32/float-little>>,
720                        X end.",
721                2.0),
722    check(fun() -> <<X:32/float-native>> = <<2.0:32/float-native>>,
723                         X end,
724                "begin <<X:32/float-native>> = <<2.0:32/float-native>>,
725                        X end.",
726                2.0),
727
728    check(
729            fun() ->
730                    [X || <<"hej",X:8>> <= <<"hej",8,"san",9,"hej",17,"hej">>]
731            end,
732            "[X || <<\"hej\",X:8>> <=
733                        <<\"hej\",8,\"san\",9,\"hej\",17,\"hej\">>].",
734            [8,17]),
735    check(
736            fun() ->
737                    L = 8, << <<B:32>> || <<L:L,B:L>> <= <<16:8, 7:16>> >>
738            end,
739            "begin L = 8, << <<B:32>> || <<L:L,B:L>> <= <<16:8, 7:16>> >>
740             end.",
741            <<0,0,0,7>>),
742    %% Test the Value part of a binary segment.
743    %% "Old" bugs have been fixed (partial_eval is called on Value).
744    check(fun() -> [ 3 || <<17/float>> <= <<17.0/float>>] end,
745                "[ 3 || <<17/float>> <= <<17.0/float>>].",
746                [3]),
747    check(fun() -> [ 3 || <<17/float>> <- [<<17.0/float>>]] end,
748                "[ 3 || <<17/float>> <- [<<17.0/float>>]].",
749                [3]),
750    check(fun() -> [ X || <<17/float,X:3>> <= <<17.0/float,2:3>>] end,
751                "[ X || <<17/float,X:3>> <= <<17.0/float,2:3>>].",
752                [2]),
753    check(fun() ->
754                 [ foo || <<(1 bsl 1023)/float>> <= <<(1 bsl 1023)/float>>]
755                end,
756                "[ foo || <<(1 bsl 1023)/float>> <= <<(1 bsl 1023)/float>>].",
757                [foo]),
758    check(fun() ->
759                 [ foo || <<(1 bsl 1023)/float>> <- [<<(1 bsl 1023)/float>>]]
760                end,
761               "[ foo || <<(1 bsl 1023)/float>> <- [<<(1 bsl 1023)/float>>]].",
762                [foo]),
763    error_check("[ foo || <<(1 bsl 1024)/float>> <-
764                            [<<(1 bsl 1024)/float>>]].",
765                      badarg),
766    check(fun() ->
767                 [ foo || <<(1 bsl 1024)/float>> <- [<<(1 bsl 1023)/float>>]]
768                end,
769                "[ foo || <<(1 bsl 1024)/float>> <-
770                            [<<(1 bsl 1023)/float>>]].",
771                []),
772    check(fun() ->
773                 [ foo || <<(1 bsl 1024)/float>> <= <<(1 bsl 1023)/float>>]
774                end,
775                "[ foo || <<(1 bsl 1024)/float>> <=
776                            <<(1 bsl 1023)/float>>].",
777                []),
778    check(fun() ->
779                        L = 8,
780                        [{L,B} || <<L:L,B:L/float>> <= <<32:8,7:32/float>>]
781                end,
782                "begin L = 8,
783                       [{L,B} || <<L:L,B:L/float>> <= <<32:8,7:32/float>>]
784                 end.",
785                [{32,7.0}]),
786    check(fun() ->
787                        L = 8,
788                        [{L,B} || <<L:L,B:L/float>> <- [<<32:8,7:32/float>>]]
789                end,
790                "begin L = 8,
791                       [{L,B} || <<L:L,B:L/float>> <- [<<32:8,7:32/float>>]]
792                 end.",
793                [{32,7.0}]),
794    check(fun() ->
795                        [foo || <<"s">> <= <<"st">>]
796                end,
797                "[foo || <<\"s\">> <= <<\"st\">>].",
798                [foo]),
799    check(fun() -> <<_:32>> = <<17:32>> end,
800                "<<_:32>> = <<17:32>>.",
801                <<17:32>>),
802    check(fun() -> [foo || <<_:32>> <= <<17:32,20:32>>] end,
803                "[foo || <<_:32>> <= <<17:32,20:32>>].",
804                [foo,foo]),
805
806    check(fun() -> << <<X:32>> || X <- [1,2,3], X > 1 >> end,
807                "<< <<X:32>> || X <- [1,2,3], X > 1 >>.",
808                <<0,0,0,2,0,0,0,3>>),
809    error_check("[X || <<X>> <= [a,b]].",{bad_generator,[a,b]}),
810    ok.
811
812%% OTP-6787. bitlevel binaries.
813otp_6787(Config) when is_list(Config) ->
814    check(
815            fun() -> <<16:(1024*1024)>> = <<16:(1024*1024)>> end,
816            "<<16:(1024*1024)>> = <<16:(1024*1024)>>.",
817            <<16:1048576>>),
818    ok.
819
820%% OTP-6977. ++ bug.
821otp_6977(Config) when is_list(Config) ->
822    check(
823            fun() -> (fun([$X] ++ _) -> ok end)("X") end,
824            "(fun([$X] ++ _) -> ok end)(\"X\").",
825            ok),
826    ok.
827
828%% OTP-7550. Support for UTF-8, UTF-16, UTF-32.
829otp_7550(Config) when is_list(Config) ->
830
831    %% UTF-8.
832    check(
833	    fun() -> <<65>> = <<65/utf8>> end,
834	    "<<65>> = <<65/utf8>>.",
835	    <<65>>),
836    check(
837	    fun() -> <<350/utf8>> = <<197,158>> end,
838	    "<<350/utf8>> = <<197,158>>.",
839	    <<197,158>>),
840    check(
841	    fun() -> <<$b,$j,$\303,$\266,$r,$n>> = <<"bj\366rn"/utf8>> end,
842	    "<<$b,$j,$\303,$\266,$r,$n>> = <<\"bj\366rn\"/utf8>>.",
843	    <<$b,$j,$\303,$\266,$r,$n>>),
844
845    %% UTF-16.
846    check(
847	    fun() -> <<0,65>> = <<65/utf16>> end,
848	    "<<0,65>> = <<65/utf16>>.",
849	    <<0,65>>),
850    check(
851	    fun() -> <<16#D8,16#08,16#DF,16#45>> = <<16#12345/utf16>> end,
852	    "<<16#D8,16#08,16#DF,16#45>> = <<16#12345/utf16>>.",
853	    <<16#D8,16#08,16#DF,16#45>>),
854    check(
855	    fun() -> <<16#08,16#D8,16#45,16#DF>> = <<16#12345/little-utf16>> end,
856	    "<<16#08,16#D8,16#45,16#DF>> = <<16#12345/little-utf16>>.",
857	    <<16#08,16#D8,16#45,16#DF>>),
858
859    check(
860	    fun() -> <<350/utf16>> = <<1,94>> end,
861	    "<<350/utf16>> = <<1,94>>.",
862	    <<1,94>>),
863    check(
864	    fun() -> <<350/little-utf16>> = <<94,1>> end,
865	    "<<350/little-utf16>> = <<94,1>>.",
866	    <<94,1>>),
867    check(
868	    fun() -> <<16#12345/utf16>> = <<16#D8,16#08,16#DF,16#45>> end,
869	    "<<16#12345/utf16>> = <<16#D8,16#08,16#DF,16#45>>.",
870	    <<16#D8,16#08,16#DF,16#45>>),
871    check(
872	    fun() -> <<16#12345/little-utf16>> = <<16#08,16#D8,16#45,16#DF>> end,
873	    "<<16#12345/little-utf16>> = <<16#08,16#D8,16#45,16#DF>>.",
874	    <<16#08,16#D8,16#45,16#DF>>),
875
876    %% UTF-32.
877    check(
878	    fun() -> <<16#12345/utf32>> = <<16#0,16#01,16#23,16#45>> end,
879	    "<<16#12345/utf32>> = <<16#0,16#01,16#23,16#45>>.",
880	    <<16#0,16#01,16#23,16#45>>),
881    check(
882	    fun() -> <<16#0,16#01,16#23,16#45>> = <<16#12345/utf32>> end,
883	    "<<16#0,16#01,16#23,16#45>> = <<16#12345/utf32>>.",
884	    <<16#0,16#01,16#23,16#45>>),
885    check(
886	    fun() -> <<16#12345/little-utf32>> = <<16#45,16#23,16#01,16#00>> end,
887	    "<<16#12345/little-utf32>> = <<16#45,16#23,16#01,16#00>>.",
888	    <<16#45,16#23,16#01,16#00>>),
889    check(
890	    fun() -> <<16#12345/little-utf32>> end,
891	    "<<16#12345/little-utf32>>.",
892	    <<16#45,16#23,16#01,16#00>>),
893
894    %% Mixed.
895    check(
896	    fun() -> <<16#41,16#12345/utf32,16#0391:16,16#2E:8>> end,
897	    "<<16#41,16#12345/utf32,16#0391:16,16#2E:8>>.",
898	    <<16#41,16#00,16#01,16#23,16#45,16#03,16#91,16#2E>>),
899    ok.
900
901
902%% OTP-8133. Bit comprehension bug.
903otp_8133(Config) when is_list(Config) ->
904    check(
905            fun() ->
906                  E = fun(N) ->
907                              if
908                                  is_integer(N) -> <<N/integer>>;
909                                  true -> throw(foo)
910                              end
911                      end,
912                  try << << (E(V))/binary >> || V <- [1,2,3,a] >>
913                  catch foo -> ok
914                  end
915            end,
916            "begin
917                 E = fun(N) ->
918                            if is_integer(N) -> <<N/integer>>;
919                               true -> throw(foo)
920                            end
921                     end,
922                 try << << (E(V))/binary >> || V <- [1,2,3,a] >>
923                 catch foo -> ok
924                 end
925             end.",
926            ok),
927    check(
928            fun() ->
929                  E = fun(N) ->
930                              if
931                                  is_integer(N) -> <<N/integer>>;
932
933                                  true -> erlang:error(foo)
934                              end
935                      end,
936                  try << << (E(V))/binary >> || V <- [1,2,3,a] >>
937                  catch error:foo -> ok
938                  end
939            end,
940            "begin
941                 E = fun(N) ->
942                            if is_integer(N) -> <<N/integer>>;
943                               true -> erlang:error(foo)
944                            end
945                     end,
946                 try << << (E(V))/binary >> || V <- [1,2,3,a] >>
947                 catch error:foo -> ok
948                 end
949             end.",
950            ok),
951    ok.
952
953%% OTP-10622. Bugs.
954otp_10622(Config) when is_list(Config) ->
955    check(fun() -> <<0>> = <<"\x{400}">> end,
956          "<<0>> = <<\"\\x{400}\">>. ",
957          <<0>>),
958    check(fun() -> <<"\x{aa}ff"/utf8>> = <<"\x{aa}ff"/utf8>> end,
959          "<<\"\\x{aa}ff\"/utf8>> = <<\"\\x{aa}ff\"/utf8>>. ",
960          <<"Â\xaaff">>),
961    %% The same bug as last example:
962    check(fun() -> case <<"foo"/utf8>> of
963                       <<"foo"/utf8>> -> true
964                   end
965          end,
966          "case <<\"foo\"/utf8>> of <<\"foo\"/utf8>> -> true end.",
967          true),
968    check(fun() -> <<"\x{400}"/utf8>> = <<"\x{400}"/utf8>> end,
969          "<<\"\\x{400}\"/utf8>> = <<\"\\x{400}\"/utf8>>. ",
970          <<208,128>>),
971    error_check("<<\"\\x{aaa}\">> = <<\"\\x{aaa}\">>.",
972                {badmatch,<<"\xaa">>}),
973
974    check(fun() -> [a || <<"\x{aaa}">> <= <<2703:16>>] end,
975          "[a || <<\"\\x{aaa}\">> <= <<2703:16>>]. ",
976          []),
977    check(fun() -> [a || <<"\x{aa}"/utf8>> <= <<"\x{aa}"/utf8>>] end,
978          "[a || <<\"\\x{aa}\"/utf8>> <= <<\"\\x{aa}\"/utf8>>]. ",
979          [a]),
980    check(fun() -> [a || <<"\x{aa}x"/utf8>> <= <<"\x{aa}y"/utf8>>] end,
981          "[a || <<\"\\x{aa}x\"/utf8>> <= <<\"\\x{aa}y\"/utf8>>]. ",
982          []),
983    check(fun() -> [a || <<"\x{aaa}">> <= <<"\x{aaa}">>] end,
984          "[a || <<\"\\x{aaa}\">> <= <<\"\\x{aaa}\">>]. ",
985          []),
986    check(fun() -> [a || <<"\x{aaa}"/utf8>> <= <<"\x{aaa}"/utf8>>] end,
987          "[a || <<\"\\x{aaa}\"/utf8>> <= <<\"\\x{aaa}\"/utf8>>]. ",
988          [a]),
989
990    ok.
991
992%% OTP-13228. ERL-32: non-local function handler bug.
993otp_13228(_Config) ->
994    LFH = {value, fun(foo, [io_fwrite]) -> worked end},
995    EFH = {value, fun({io, fwrite}, [atom]) -> io_fwrite end},
996    {value, worked, []} = parse_and_run("foo(io:fwrite(atom)).", LFH, EFH).
997
998%% OTP-14826: more accurate stacktrace.
999otp_14826(_Config) ->
1000    backtrace_check("fun(P) when is_pid(P) -> true end(a).",
1001                    function_clause,
1002                    [{erl_eval,'-inside-an-interpreted-fun-',[a],[]},
1003                     {erl_eval,eval_fun,6},
1004                     ?MODULE]),
1005    backtrace_check("B.",
1006                    {unbound_var, 'B'},
1007                    [{erl_eval,expr,2}, ?MODULE]),
1008    backtrace_check("B.",
1009                    {unbound, 'B'},
1010                    [{erl_eval,expr,5}, ?MODULE],
1011                    none, none),
1012    backtrace_check("1/0.",
1013                    badarith,
1014                    [{erlang,'/',[1,0],[]},
1015                     {erl_eval,do_apply,6}]),
1016    backtrace_catch("catch 1/0.",
1017                    badarith,
1018                    [{erlang,'/',[1,0],[]},
1019                     {erl_eval,do_apply,6}]),
1020    check(fun() -> catch exit(foo) end,
1021          "catch exit(foo).",
1022          {'EXIT', foo}),
1023    check(fun() -> catch throw(foo) end,
1024          "catch throw(foo).",
1025          foo),
1026    backtrace_check("try 1/0 after foo end.",
1027                    badarith,
1028                    [{erlang,'/',[1,0],[]},
1029                     {erl_eval,do_apply,6}]),
1030    backtrace_catch("catch (try 1/0 after foo end).",
1031                    badarith,
1032                    [{erlang,'/',[1,0],[]},
1033                     {erl_eval,do_apply,6}]),
1034    backtrace_catch("try catch 1/0 after foo end.",
1035                    badarith,
1036                    [{erlang,'/',[1,0],[]},
1037                     {erl_eval,do_apply,6}]),
1038    backtrace_check("try a of b -> bar after foo end.",
1039                    {try_clause,a},
1040                    [{erl_eval,try_clauses,8}]),
1041    check(fun() -> X = try foo:bar() catch A:B:C -> {A,B} end, X end,
1042          "try foo:bar() catch A:B:C -> {A,B} end.",
1043          {error, undef}),
1044    backtrace_check("C = 4, try foo:bar() catch A:B:C -> {A,B,C} end.",
1045                    stacktrace_bound,
1046                    [{erl_eval,check_stacktrace_vars,2},
1047                     {erl_eval,try_clauses,8}],
1048                    none, none),
1049    backtrace_catch("catch (try a of b -> bar after foo end).",
1050                    {try_clause,a},
1051                    [{erl_eval,try_clauses,8}]),
1052    backtrace_check("try 1/0 catch exit:a -> foo end.",
1053                    badarith,
1054                    [{erlang,'/',[1,0],[]},
1055                     {erl_eval,do_apply,6}]),
1056    Es = [{'try',1,[{call,1,{remote,1,{atom,1,foo},{atom,1,bar}},[]}],
1057           [],
1058           [{clause,1,[{tuple,1,[{var,1,'A'},{var,1,'B'},{atom,1,'C'}]}],
1059             [],[{tuple,1,[{var,1,'A'},{var,1,'B'},{atom,1,'C'}]}]}],[]}],
1060    try
1061        erl_eval:exprs(Es, [], none, none),
1062        ct:fail(stacktrace_variable)
1063    catch
1064        error:{illegal_stacktrace_variable,{atom,1,'C'}}:S ->
1065            [{erl_eval,check_stacktrace_vars,2,_},
1066             {erl_eval,try_clauses,8,_}|_] = S
1067    end,
1068    backtrace_check("{1,1} = {A = 1, A = 2}.",
1069                    {badmatch, 1},
1070                    [erl_eval, {lists,foldl,3}]),
1071    backtrace_check("case a of a when foo:bar() -> x end.",
1072                    guard_expr,
1073                    [{erl_eval,guard0,4}], none, none),
1074    backtrace_check("case a of foo() -> ok end.",
1075                    {illegal_pattern,{call,1,{atom,1,foo},[]}},
1076                    [{erl_eval,match,4}], none, none),
1077    backtrace_check("case a of b -> ok end.",
1078                    {case_clause,a},
1079                    [{erl_eval,case_clauses,6}, ?MODULE]),
1080    backtrace_check("if a =:= b -> ok end.",
1081                    if_clause,
1082                    [{erl_eval,if_clauses,5}, ?MODULE]),
1083    backtrace_check("fun A(b) -> ok end(a).",
1084                    function_clause,
1085                    [{erl_eval,'-inside-an-interpreted-fun-',[a],[]},
1086                     {erl_eval,eval_named_fun,8},
1087                     ?MODULE]),
1088    backtrace_check("[A || A <- a].",
1089                    {bad_generator, a},
1090                    [{erl_eval,eval_generate,7}, {erl_eval, eval_lc, 6}]),
1091    backtrace_check("<< <<A>> || <<A>> <= a>>.",
1092                    {bad_generator, a},
1093                    [{erl_eval,eval_b_generate,7}, {erl_eval, eval_bc, 6}]),
1094    backtrace_check("[A || A <- [1], begin a end].",
1095                    {bad_filter, a},
1096                    [{erl_eval,eval_filter,6}, {erl_eval, eval_generate, 7}]),
1097    fun() ->
1098            {'EXIT', {{badarity, {_Fun, []}}, BT}} =
1099                (catch parse_and_run("fun(A) -> A end().")),
1100            check_backtrace([{erl_eval,do_apply,5}, ?MODULE], BT)
1101    end(),
1102    fun() ->
1103            {'EXIT', {{badarity, {_Fun, []}}, BT}} =
1104                (catch parse_and_run("fun F(A) -> A end().")),
1105            check_backtrace([{erl_eval,do_apply,5}, ?MODULE], BT)
1106    end(),
1107    backtrace_check("foo().",
1108                    undef,
1109                    [{erl_eval,foo,0},{erl_eval,local_func,6}],
1110                    none, none),
1111    backtrace_check("a orelse false.",
1112                    {badarg, a},
1113                    [{erl_eval,expr,5}, ?MODULE]),
1114    backtrace_check("a andalso false.",
1115                    {badarg, a},
1116                    [{erl_eval,expr,5}, ?MODULE]),
1117    backtrace_check("t = u.",
1118                    {badmatch, u},
1119                    [{erl_eval,expr,5}, ?MODULE]),
1120    backtrace_check("{math,sqrt}(2).",
1121                    {badfun, {math,sqrt}},
1122                    [{erl_eval,expr,5}, ?MODULE]),
1123    backtrace_check("erl_eval_SUITE:simple().",
1124                    simple,
1125                    [{?MODULE,simple1,0},{?MODULE,simple,0},erl_eval]),
1126    Args = [{integer,1,I} || I <- lists:seq(1, 30)],
1127    backtrace_check("fun(1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,"
1128                    "19,20,21,22,23,24,25,26,27,28,29,30) -> a end.",
1129                    {argument_limit,
1130                     {'fun',1,[{clause,1,Args,[],[{atom,1,a}]}]}},
1131                    [{erl_eval,expr,5}, ?MODULE]),
1132    backtrace_check("fun F(1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,"
1133                    "19,20,21,22,23,24,25,26,27,28,29,30) -> a end.",
1134                    {argument_limit,
1135                     {named_fun,1,'F',[{clause,1,Args,[],[{atom,1,a}]}]}},
1136                    [{erl_eval,expr,5}, ?MODULE]),
1137    backtrace_check("#r{}.",
1138                    {undef_record,r},
1139                    [{erl_eval,expr,5}, ?MODULE],
1140                    none, none),
1141    %% eval_bits
1142    backtrace_check("<<100:8/bitstring>>.",
1143                    badarg,
1144                    [{eval_bits,eval_exp_field1,6},
1145                     eval_bits,eval_bits,erl_eval]),
1146    backtrace_check("<<100:8/foo>>.",
1147                    {undefined_bittype,foo},
1148                    [{eval_bits,make_bit_type,3},eval_bits,
1149                     eval_bits,eval_bits],
1150                    none, none),
1151    backtrace_check("B = <<\"foo\">>, <<B/binary-unit:7>>.",
1152                    badarg,
1153                    [{eval_bits,eval_exp_field1,6},
1154                     eval_bits,eval_bits,erl_eval],
1155                    none, none),
1156    ok.
1157
1158simple() ->
1159    A = simple1(),
1160    {A}.
1161
1162simple1() ->
1163    %% If the compiler could see that this function would always
1164    %% throw an error exception, it would rewrite simple() like this:
1165    %%
1166    %%   simple() -> simple1().
1167    %%
1168    %% That would change the stacktrace. To prevent the compiler from
1169    %% doing that optimization, we must obfuscate the code.
1170    case get(a_key_that_is_not_defined) of
1171        undefined -> erlang:error(simple);
1172        WillNeverHappen -> WillNeverHappen
1173    end.
1174
1175%% Simple cases, just to cover some code.
1176funs(Config) when is_list(Config) ->
1177    do_funs(none, none),
1178    do_funs(lfh(), none),
1179    do_funs(lfh(), efh()),
1180
1181    error_check("nix:foo().", {access_not_allowed,nix}, lfh(), efh()),
1182    error_check("bar().", undef, none, none),
1183
1184    check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
1185                         F1(F1, 1000) end,
1186                "begin F1 = fun(F,N) -> count_down(F, N) end,"
1187                "F1(F1,1000) end.",
1188		0, ['F1'], lfh(), none),
1189
1190    check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
1191                         F1(F1, 1000) end,
1192                "begin F1 = fun(F,N) -> count_down(F, N) end,"
1193                "F1(F1,1000) end.",
1194		0, ['F1'], lfh_value(), none),
1195
1196    check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
1197                         F1(F1, 1000) end,
1198                "begin F1 = fun(F,N) -> count_down(F, N) end,"
1199                "F1(F1,1000) end.",
1200		0, ['F1'], lfh_value_extra(), none),
1201
1202    check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
1203                         F1(F1, 1000) end,
1204                "begin F1 = fun(F,N) -> count_down(F, N) end,"
1205                "F1(F1,1000) end.",
1206		0, ['F1'], {?MODULE,local_func_value}, none),
1207    %% This is not documented, and only for backward compatibility (good!).
1208    B0 = erl_eval:new_bindings(),
1209    check(fun() -> is_function(?MODULE:count_down_fun()) end,
1210                "begin is_function(count_down_fun()) end.",
1211                true, [], {?MODULE,local_func,[B0]},none),
1212
1213    EF = fun({timer,sleep}, As) when length(As) == 1 -> exit({got_it,sleep});
1214            ({M,F}, As) -> apply(M, F, As)
1215         end,
1216    EFH = {value, EF},
1217    error_check("apply(timer, sleep, [1]).", got_it, none, EFH),
1218    error_check("begin F = fun(T) -> timer:sleep(T) end,F(1) end.",
1219                      got_it, none, EFH),
1220    error_check("fun c/1.", undef),
1221    error_check("fun a:b/0().", undef),
1222
1223    MaxArgs = 20,
1224    [true] =
1225        lists:usort([run_many_args(SAs) || SAs <- many_args(MaxArgs)]),
1226    {'EXIT',{{argument_limit,_},_}} =
1227        (catch run_many_args(many_args1(MaxArgs+1))),
1228
1229    check(fun() -> M = lists, F = fun M:reverse/1,
1230			 [1,2] = F([2,1]), ok end,
1231		"begin M = lists, F = fun M:reverse/1,"
1232		" [1,2] = F([2,1]), ok end.",
1233		ok),
1234
1235    %% Test that {M,F} is not accepted as a fun.
1236    error_check("{" ?MODULE_STRING ",module_info}().",
1237		{badfun,{?MODULE,module_info}}),
1238    ok.
1239
1240run_many_args({S, As}) ->
1241    apply(eval_string(S), As) =:= As.
1242
1243many_args(N) ->
1244    [many_args1(I) || I <- lists:seq(1, N)].
1245
1246many_args1(N) ->
1247    F = fun(L, P) ->
1248                tl(lists:flatten([","++P++integer_to_list(E) || E <- L]))
1249        end,
1250    L = lists:seq(1, N),
1251    T = F(L, "V"),
1252    S = lists:flatten(io_lib:format("fun(~s) -> [~s] end.", [T, T])),
1253    {S, L}.
1254
1255do_funs(LFH, EFH) ->
1256    %% LFH is not really used by these examples...
1257
1258    %% These tests do not prove that tail recursive functions really
1259    %% work (that the process does not grow); one should also run them
1260    %% manually with 1000 replaced by 1000000.
1261
1262    M = atom_to_list(?MODULE),
1263    check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
1264                         F1(F1, 1000) end,
1265                concat(["begin F1 = fun(F,N) -> ", M,
1266                        ":count_down(F, N) end, F1(F1,1000) end."]),
1267		0, ['F1'], LFH, EFH),
1268    check(fun() -> F1 = fun(F,N) -> apply(?MODULE,count_down,[F,N])
1269                              end, F1(F1, 1000) end,
1270                concat(["begin F1 = fun(F,N) -> apply(", M,
1271                        ",count_down,[F, N]) end, F1(F1,1000) end."]),
1272		0, ['F1'], LFH, EFH),
1273    check(fun() -> F = fun(F,N) when N > 0 -> apply(F,[F,N-1]);
1274                                (_F,0) -> ok end,
1275                         F(F, 1000)
1276                end,
1277                "begin F = fun(F,N) when N > 0 -> apply(F,[F,N-1]);"
1278                             "(_F,0) -> ok end,"
1279                       "F(F, 1000) end.",
1280                ok, ['F'], LFH, EFH),
1281    check(fun() -> F = fun(F,N) when N > 0 ->
1282                                     apply(erlang,apply,[F,[F,N-1]]);
1283                                (_F,0) -> ok end,
1284                         F(F, 1000)
1285                end,
1286                "begin F = fun(F,N) when N > 0 ->"
1287                                   "apply(erlang,apply,[F,[F,N-1]]);"
1288                             "(_F,0) -> ok end,"
1289                       "F(F, 1000) end.",
1290                ok, ['F'], LFH, EFH),
1291    check(fun() -> F = count_down_fun(),
1292                         SF = fun(SF, F1, N) -> F(SF, F1, N) end,
1293                         SF(SF, F, 1000) end,
1294                concat(["begin F = ", M, ":count_down_fun(),"
1295                        "SF = fun(SF, F1, N) -> F(SF, F1, N) end,"
1296                        "SF(SF, F, 1000) end."]),
1297                ok, ['F','SF'], LFH, EFH),
1298
1299
1300    check(fun() -> F = fun(X) -> A = 1+X, {X,A} end,
1301                         true = {2,3} == F(2) end,
1302                "begin F = fun(X) -> A = 1+X, {X,A} end,
1303                       true = {2,3} == F(2) end.", true, ['F'], LFH, EFH),
1304    check(fun() -> F = fun(X) -> erlang:'+'(X,2) end,
1305		   true = 3 == F(1) end,
1306	  "begin F = fun(X) -> erlang:'+'(X,2) end,"
1307	  "      true = 3 == F(1) end.", true, ['F'],
1308	  LFH, EFH),
1309    check(fun() -> F = fun(X) -> byte_size(X) end,
1310                         ?MODULE:do_apply(F,<<"hej">>) end,
1311                concat(["begin F = fun(X) -> size(X) end,",
1312                        M,":do_apply(F,<<\"hej\">>) end."]),
1313                3, ['F'], LFH, EFH),
1314
1315    check(fun() -> F1 = fun(X, Z) -> {X,Z} end,
1316                         Z = 5,
1317                         F2 = fun(X, Y) -> F1(Z,{X,Y}) end,
1318                         F3 = fun(X, Y) -> {a,F1(Z,{X,Y})} end,
1319                         {5,{x,y}} = F2(x,y),
1320                         {a,{5,{y,x}}} = F3(y,x),
1321                         {5,{5,y}} = F2(Z,y),
1322                         true = {5,{x,5}} == F2(x,Z) end,
1323                "begin F1 = fun(X, Z) -> {X,Z} end,
1324                       Z = 5,
1325                       F2 = fun(X, Y) -> F1(Z,{X,Y}) end,
1326                       F3 = fun(X, Y) -> {a,F1(Z,{X,Y})} end,
1327                       {5,{x,y}} = F2(x,y),
1328                       {a,{5,{y,x}}} = F3(y,x),
1329                       {5,{5,y}} = F2(Z,y),
1330                       true = {5,{x,5}} == F2(x,Z) end.",
1331                true, ['F1','Z','F2','F3'], LFH, EFH),
1332    check(fun() -> F = fun(X) -> byte_size(X) end,
1333                         F2 = fun(Y) -> F(Y) end,
1334                         ?MODULE:do_apply(F2,<<"hej">>) end,
1335                concat(["begin F = fun(X) -> size(X) end,",
1336                        "F2 = fun(Y) -> F(Y) end,",
1337                        M,":do_apply(F2,<<\"hej\">>) end."]),
1338                3, ['F','F2'], LFH, EFH),
1339    check(fun() -> Z = 5, F = fun(X) -> {Z,X} end,
1340                         F2 = fun(Z) -> F(Z) end, F2(3) end,
1341                "begin Z = 5, F = fun(X) -> {Z,X} end,
1342                       F2 = fun(Z) -> F(Z) end, F2(3) end.",
1343                {5,3},['F','F2','Z'], LFH, EFH),
1344    check(fun() -> F = fun(Z) -> Z end,
1345                         F2 = fun(X) -> F(X), Z = {X,X}, Z end,
1346                         {1,1} = F2(1), Z = 7, Z end,
1347                "begin F = fun(Z) -> Z end,
1348                       F2 = fun(X) -> F(X), Z = {X,X}, Z end,
1349                       {1,1} = F2(1), Z = 7, Z end.", 7, ['F','F2','Z'],
1350                LFH, EFH),
1351    check(fun() -> F = fun(F, N) -> [?MODULE:count_down(F,N) || X <-[1]]
1352                             end, F(F,2) end,
1353                concat(["begin F = fun(F, N) -> [", M,
1354                       ":count_down(F,N) || X <-[1]] end, F(F,2) end."]),
1355                [[[0]]], ['F'], LFH, EFH),
1356    ok.
1357
1358count_down(F, N) when N > 0 ->
1359    F(F, N-1);
1360count_down(_F, N) ->
1361    N.
1362
1363count_down_fun() ->
1364    fun(SF,F,N) when N > 0 -> SF(SF,F,N-1);
1365       (_SF,_F,_N) -> ok
1366    end.
1367
1368do_apply(F, V) ->
1369    F(V).
1370
1371lfh() ->
1372    {eval, fun(F, As, Bs) -> local_func(F, As, Bs) end}.
1373
1374local_func(F, As0, Bs0) when is_atom(F) ->
1375    {As,Bs} = erl_eval:expr_list(As0, Bs0, lfh()),
1376    case erlang:function_exported(?MODULE, F, length(As)) of
1377	true ->
1378	    {value,apply(?MODULE, F, As),Bs};
1379	false ->
1380	    {value,apply(shell_default, F, As),Bs}
1381    end.
1382
1383lfh_value_extra() ->
1384    %% Not documented.
1385    {value, fun(F, As, a1, a2) -> local_func_value(F, As) end, [a1, a2]}.
1386
1387lfh_value() ->
1388    {value, fun(F, As) -> local_func_value(F, As) end}.
1389
1390local_func_value(F, As) when is_atom(F) ->
1391    case erlang:function_exported(?MODULE, F, length(As)) of
1392	true ->
1393	    apply(?MODULE, F, As);
1394	false ->
1395	    apply(shell_default, F, As)
1396    end.
1397
1398efh() ->
1399    {value, fun(F, As) -> external_func(F, As) end}.
1400
1401external_func({M,_}, _As) when M == nix ->
1402    exit({{access_not_allowed,M},[mfa]});
1403external_func(F, As) when is_function(F) ->
1404    apply(F, As);
1405external_func({M,F}, As) ->
1406    apply(M, F, As).
1407
1408
1409
1410%% Test try-of-catch-after-end statement.
1411try_catch(Config) when is_list(Config) ->
1412    %% Match in of with catch
1413    check(fun() -> try 1 of 1 -> 2 catch _:_ -> 3 end end,
1414		"try 1 of 1 -> 2 catch _:_ -> 3 end.", 2),
1415    check(fun() -> try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
1416		"try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end.", 2),
1417    check(fun() -> try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
1418		"try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end.", 4),
1419    %% Just after
1420    check(fun () -> X = try 1 after put(try_catch, 2) end,
1421			  {X,get(try_catch)} end,
1422		"begin X = try 1 after put(try_catch, 2) end, "
1423		"{X,get(try_catch)} end.", {1,2}),
1424    %% Match in of with after
1425    check(fun() -> X = try 1 of 1 -> 2 after put(try_catch, 3) end,
1426			 {X,get(try_catch)} end,
1427		"begin X = try 1 of 1 -> 2 after put(try_catch, 3) end, "
1428		"{X,get(try_catch)} end.", {2,3}),
1429    check(fun() -> X = try 1 of 1 -> 2; 3 -> 4
1430			     after put(try_catch, 5) end,
1431			 {X,get(try_catch)} end,
1432		"begin X = try 1 of 1 -> 2; 3 -> 4 "
1433		"          after put(try_catch, 5) end, "
1434		"      {X,get(try_catch)} end.", {2,5}),
1435    check(fun() -> X = try 3 of 1 -> 2; 3 -> 4
1436			     after put(try_catch, 5) end,
1437			 {X,get(try_catch)} end,
1438		"begin X = try 3 of 1 -> 2; 3 -> 4 "
1439		"          after put(try_catch, 5) end, "
1440		"      {X,get(try_catch)} end.", {4,5}),
1441    %% Nomatch in of
1442    error_check("try 1 of 2 -> 3 catch _:_ -> 4 end.",
1443		      {try_clause,1}),
1444    %% Nomatch in of with after
1445    check(fun () -> {'EXIT',{{try_clause,1},_}} =
1446			      begin catch try 1 of 2 -> 3
1447				          after put(try_catch, 4) end end,
1448			  get(try_catch) end,
1449		"begin {'EXIT',{{try_clause,1},_}} = "
1450		"          begin catch try 1 of 2 -> 3 "
1451		"                      after put(try_catch, 4) end end, "
1452		"      get(try_catch) end. ", 4),
1453    %% Exception in try
1454    check(fun () -> try 1=2 catch error:{badmatch,2} -> 3 end end,
1455		"try 1=2 catch error:{badmatch,2} -> 3 end.", 3),
1456    check(fun () -> try 1=2 of 3 -> 4
1457			  catch error:{badmatch,2} -> 5 end end,
1458		"try 1=2 of 3 -> 4 "
1459		"catch error:{badmatch,2} -> 5 end.", 5),
1460    %% Exception in try with after
1461    check(fun () -> X = try 1=2
1462			      catch error:{badmatch,2} -> 3
1463			      after put(try_catch, 4) end,
1464			  {X,get(try_catch)} end,
1465		"begin X = try 1=2 "
1466		"          catch error:{badmatch,2} -> 3 "
1467		"          after put(try_catch, 4) end, "
1468		"      {X,get(try_catch)} end. ", {3,4}),
1469    check(fun () -> X = try 1=2 of 3 -> 4
1470			      catch error:{badmatch,2} -> 5
1471			      after put(try_catch, 6) end,
1472			  {X,get(try_catch)} end,
1473		"begin X = try 1=2 of 3 -> 4"
1474		"          catch error:{badmatch,2} -> 5 "
1475		"          after put(try_catch, 6) end, "
1476		"      {X,get(try_catch)} end. ", {5,6}),
1477    %% Uncaught exception
1478    error_check("try 1=2 catch error:undefined -> 3 end. ",
1479		      {badmatch,2}),
1480    error_check("try 1=2 of 3 -> 4 catch error:undefined -> 5 end. ",
1481		      {badmatch,2}),
1482    %% Uncaught exception with after
1483    check(fun () -> {'EXIT',{{badmatch,2},_}} =
1484			      begin catch try 1=2
1485					  after put(try_catch, 3) end end,
1486			  get(try_catch) end,
1487		"begin {'EXIT',{{badmatch,2},_}} = "
1488		"          begin catch try 1=2 "
1489		"                      after put(try_catch, 3) end end, "
1490		"      get(try_catch) end. ", 3),
1491    check(fun () -> {'EXIT',{{badmatch,2},_}} =
1492			      begin catch try 1=2 of 3 -> 4
1493					  after put(try_catch, 5) end end,
1494			  get(try_catch) end,
1495		"begin {'EXIT',{{badmatch,2},_}} = "
1496		"          begin catch try 1=2 of 3 -> 4"
1497		"                      after put(try_catch, 5) end end, "
1498		"      get(try_catch) end. ", 5),
1499    check(fun () -> {'EXIT',{{badmatch,2},_}} =
1500			      begin catch try 1=2 catch error:undefined -> 3
1501					  after put(try_catch, 4) end end,
1502			  get(try_catch) end,
1503		"begin {'EXIT',{{badmatch,2},_}} = "
1504		"          begin catch try 1=2 catch error:undefined -> 3 "
1505		"                      after put(try_catch, 4) end end, "
1506		"      get(try_catch) end. ", 4),
1507    check(fun () -> {'EXIT',{{badmatch,2},_}} =
1508			      begin catch try 1=2 of 3 -> 4
1509					  catch error:undefined -> 5
1510					  after put(try_catch, 6) end end,
1511			  get(try_catch) end,
1512		"begin {'EXIT',{{badmatch,2},_}} = "
1513		"          begin catch try 1=2 of 3 -> 4 "
1514		"                      catch error:undefined -> 5 "
1515		"                      after put(try_catch, 6) end end, "
1516		"      get(try_catch) end. ", 6),
1517    ok.
1518
1519
1520%% OTP-7933.
1521eval_expr_5(Config) when is_list(Config) ->
1522    {ok,Tokens ,_} =
1523	erl_scan:string("if a+4 == 4 -> yes; true -> no end. "),
1524    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
1525    {value, no, []} = erl_eval:expr(Expr, [], none, none, none),
1526    no = erl_eval:expr(Expr, [], none, none, value),
1527    try
1528	erl_eval:expr(Expr, [], none, none, 4711),
1529	function_clause = should_never_reach_here
1530    catch
1531	error:function_clause ->
1532	    ok
1533    end.
1534
1535zero_width(Config) when is_list(Config) ->
1536    check(fun() ->
1537			{'EXIT',{badarg,_}} = (catch <<not_a_number:0>>),
1538			ok
1539		end, "begin {'EXIT',{badarg,_}} = (catch <<not_a_number:0>>), "
1540		"ok end.", ok),
1541    ok.
1542
1543eep37(Config) when is_list(Config) ->
1544    check(fun () -> (fun _(X) -> X end)(42) end,
1545          "(fun _(X) -> X end)(42).",
1546          42),
1547    check(fun () -> (fun _Id(X) -> X end)(42) end,
1548          "(fun _Id(X) -> X end)(42).", 42),
1549    check(fun () -> is_function((fun Self() -> Self end)(), 0) end,
1550          "is_function((fun Self() -> Self end)(), 0).",
1551          true),
1552    check(fun () ->
1553                  F = fun Fact(N) when N > 0 ->
1554                              N * Fact(N - 1);
1555                          Fact(0) ->
1556                              1
1557                       end,
1558                  F(6)
1559          end,
1560          "(fun Fact(N) when N > 0 -> N * Fact(N - 1); Fact(0) -> 1 end)(6).",
1561          720),
1562    ok.
1563
1564eep43(Config) when is_list(Config) ->
1565    check(fun () -> #{} end, " #{}.", #{}),
1566    check(fun () -> #{a => b} end, "#{a => b}.", #{a => b}),
1567    check(fun () ->
1568                  Map = #{a => b},
1569                  {Map#{a := b},Map#{a => c},Map#{d => e}}
1570          end,
1571          "begin "
1572          "    Map = #{a => B=b}, "
1573          "    {Map#{a := B},Map#{a => c},Map#{d => e}} "
1574          "end.",
1575          {#{a => b},#{a => c},#{a => b,d => e}}),
1576    check(fun () ->
1577                  lists:map(fun (X) -> X#{price := 0} end,
1578                            [#{hello => 0, price => nil}])
1579          end,
1580          "lists:map(fun (X) -> X#{price := 0} end,
1581                     [#{hello => 0, price => nil}]).",
1582          [#{hello => 0, price => 0}]),
1583    check(fun () ->
1584		Map = #{ <<33:333>> => "wat" },
1585		#{ <<33:333>> := "wat" } = Map
1586	  end,
1587	  "begin "
1588	  "   Map = #{ <<33:333>> => \"wat\" }, "
1589	  "   #{ <<33:333>> := \"wat\" } = Map  "
1590	  "end.",
1591	  #{ <<33:333>> => "wat" }),
1592    check(fun () ->
1593		K1 = 1,
1594		K2 = <<42:301>>,
1595		K3 = {3,K2},
1596		Map = #{ K1 => 1, K2 => 2, K3 => 3, {2,2} => 4},
1597		#{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map
1598	  end,
1599	  "begin "
1600	  "    K1 = 1, "
1601	  "    K2 = <<42:301>>, "
1602	  "    K3 = {3,K2}, "
1603	  "    Map = #{ K1 => 1, K2 => 2, K3 => 3, {2,2} => 4}, "
1604	  "    #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map "
1605	  "end.",
1606	  #{ 1 => 1, <<42:301>> => 2, {3,<<42:301>>} => 3, {2,2} => 4}),
1607    check(fun () ->
1608		X = key,
1609		(fun(#{X := value}) -> true end)(#{X => value})
1610	  end,
1611	  "begin "
1612	  "    X = key, "
1613	  "    (fun(#{X := value}) -> true end)(#{X => value}) "
1614	  "end.",
1615	  true),
1616
1617    error_check("[camembert]#{}.", {badmap,[camembert]}),
1618    error_check("[camembert]#{nonexisting:=v}.", {badmap,[camembert]}),
1619    error_check("#{} = 1.", {badmatch,1}),
1620    error_check("[]#{a=>error(bad)}.", bad),
1621    error_check("(#{})#{nonexisting:=value}.", {badkey,nonexisting}),
1622    ok.
1623
1624otp_15035(Config) when is_list(Config) ->
1625    check(fun() ->
1626                  fun() when #{} ->
1627                          a;
1628                     () when #{a => b} ->
1629                          b;
1630                     () when #{a => b} =:= #{a => b} ->
1631                          c
1632                  end()
1633          end,
1634          "fun() when #{} ->
1635                   a;
1636              () when #{a => b} ->
1637                   b;
1638              () when #{a => b} =:= #{a => b} ->
1639                   c
1640           end().",
1641          c),
1642    check(fun() ->
1643                  F = fun(M) when M#{} ->
1644                              a;
1645                         (M) when M#{a => b} ->
1646                              b;
1647                         (M) when M#{a := b} ->
1648                              c;
1649                         (M) when M#{a := b} =:= M#{a := b} ->
1650                              d;
1651                         (M) when M#{a => b} =:= M#{a => b} ->
1652                              e
1653                      end,
1654                  {F(#{}), F(#{a => b})}
1655          end,
1656          "fun() ->
1657                  F = fun(M) when M#{} ->
1658                              a;
1659                         (M) when M#{a => b} ->
1660                              b;
1661                         (M) when M#{a := b} ->
1662                              c;
1663                         (M) when M#{a := b} =:= M#{a := b} ->
1664                              d;
1665                         (M) when M#{a => b} =:= M#{a => b} ->
1666                              e
1667                      end,
1668                  {F(#{}), F(#{a => b})}
1669          end().",
1670          {e, d}),
1671    ok.
1672
1673otp_16439(Config) when is_list(Config) ->
1674    check(fun() -> + - 5 end, "+ - 5.", -5),
1675    check(fun() -> - + - 5 end, "- + - 5.", 5),
1676    check(fun() -> case 7 of - - 7 -> seven end end,
1677         "case 7 of - - 7 -> seven end.", seven),
1678
1679    {ok,Ts,_} = erl_scan:string("- #{}. "),
1680    A = erl_anno:new(1),
1681    {ok,[{op,A,'-',{map,A,[]}}]} = erl_parse:parse_exprs(Ts),
1682
1683    ok.
1684
1685%% Test guard expressions in keys for maps and in sizes in binary matching.
1686
1687otp_14708(Config) when is_list(Config) ->
1688    check(fun() -> X = 42, #{{tag,X} := V} = #{{tag,X} => a}, V end,
1689          "begin X = 42, #{{tag,X} := V} = #{{tag,X} => a}, V end.",
1690          a),
1691    check(fun() ->
1692                  T = {x,y,z},
1693                  Map = #{x => 99, y => 100},
1694                  #{element(1, T) := V1, element(2, T) := V2} = Map,
1695                  {V1, V2}
1696          end,
1697          "begin
1698                  T = {x,y,z},
1699                  Map = #{x => 99, y => 100},
1700                  #{element(1, T) := V1, element(2, T) := V2} = Map,
1701                  {V1, V2}
1702          end.",
1703          {99, 100}),
1704    error_check("#{term_to_binary(42) := _} = #{}.", illegal_guard_expr),
1705
1706    check(fun() ->
1707                  <<Sz:16,Body:(Sz-1)/binary>> = <<4:16,1,2,3>>,
1708                  Body
1709          end,
1710          "begin
1711              <<Sz:16,Body:(Sz-1)/binary>> = <<4:16,1,2,3>>,
1712             Body
1713          end.",
1714          <<1,2,3>>),
1715    check(fun() ->
1716                  Sizes = #{0 => 3, 1 => 7},
1717                  <<SzTag:1,Body:(map_get(SzTag, Sizes))/binary>> =
1718                      <<1:1,1,2,3,4,5,6,7>>,
1719                  Body
1720          end,
1721          "begin
1722             Sizes = #{0 => 3, 1 => 7},
1723             <<SzTag:1,Body:(map_get(SzTag, Sizes))/binary>> =
1724                 <<1:1,1,2,3,4,5,6,7>>,
1725             Body
1726          end.",
1727          <<1,2,3,4,5,6,7>>),
1728    error_check("<<X:(process_info(self()))>> = <<>>.", illegal_bitsize),
1729
1730    ok.
1731
1732otp_16545(Config) when is_list(Config) ->
1733    case eval_string("<<$W/utf16-native>> = <<$W/utf16-native>>.") of
1734        <<$W/utf16-native>> -> ok
1735    end,
1736    case eval_string("<<$W/utf32-native>> = <<$W/utf32-native>>.") of
1737        <<$W/utf32-native>> -> ok
1738    end,
1739    check(fun() -> <<10/unsigned,"fgbz":86>> end,
1740          "<<10/unsigned,\"fgbz\":86>>.",
1741          <<10,0,0,0,0,0,0,0,0,0,1,152,0,0,0,0,0,0,0,0,0,6,112,0,0,
1742            0,0,0,0,0,0,0,24,128,0,0,0,0,0,0,0,0,0,122>>),
1743    check(fun() -> <<"":16/signed>> end,
1744          "<<\"\":16/signed>>.",
1745          <<>>),
1746    error_check("<<\"\":problem/signed>>.", badarg),
1747    ok.
1748
1749otp_16865(Config) when is_list(Config) ->
1750    check(fun() -> << <<>> || <<34:(1/0)>> <= <<"string">> >> end,
1751          "<< <<>> || <<34:(1/0)>> <= <<\"string\">> >>.",
1752          <<>>),
1753    %% The order of evaluation is important. Follow the example set by
1754    %% compiled code:
1755    error_check("<< <<>> || <<>> <= <<1:(-1), (fun() -> a = b end())>> >>.",
1756                {badmatch, b}),
1757    ok.
1758
1759%% Check the string in different contexts: as is; in fun; from compiled code.
1760check(F, String, Result) ->
1761    check1(F, String, Result),
1762    FunString = concat(["fun() -> ", no_final_dot(String), " end(). "]),
1763    check1(F, FunString, Result),
1764    CompileString = concat(["hd(lists:map(fun(_) -> ", no_final_dot(String),
1765                            " end, [foo])). "]),
1766    check1(F, CompileString, Result).
1767
1768check1(F, String, Result) ->
1769    Result = F(),
1770    Expr = parse_expr(String),
1771    case catch erl_eval:expr(Expr, []) of
1772        {value, Result, Bs} when is_list(Bs) ->
1773            ok;
1774        Other1 ->
1775            ct:fail({eval, Other1, Result})
1776    end,
1777    case catch erl_eval:expr(Expr, #{}) of
1778        {value, Result, MapBs} when is_map(MapBs) ->
1779            ok;
1780        Other2 ->
1781            ct:fail({eval, Other2, Result})
1782    end.
1783
1784check(F, String, Result, BoundVars, LFH, EFH) ->
1785    Result = F(),
1786    Exprs = parse_exprs(String),
1787    case catch erl_eval:exprs(Exprs, [], LFH, EFH) of
1788        {value, Result, Bs} ->
1789            %% We just assume that Bs is an orddict...
1790            Keys = orddict:fetch_keys(Bs),
1791            case sort(BoundVars) == sort(Keys) of
1792                true ->
1793                    ok;
1794                false ->
1795                    ct:fail({check, BoundVars, Keys})
1796            end,
1797            ok;
1798        Other1 ->
1799            ct:fail({check, Other1, Result})
1800    end,
1801    case catch erl_eval:exprs(Exprs, #{}, LFH, EFH) of
1802        {value, Result, MapBs} ->
1803            MapKeys = maps:keys(MapBs),
1804            case sort(BoundVars) == sort(MapKeys) of
1805                true ->
1806                    ok;
1807                false ->
1808                    ct:fail({check, BoundVars, MapKeys})
1809            end,
1810            ok;
1811        Other2 ->
1812            ct:fail({check, Other2, Result})
1813    end.
1814
1815error_check(String, Result) ->
1816    Expr = parse_expr(String),
1817    case catch erl_eval:expr(Expr, []) of
1818        {'EXIT', {Result,_}} ->
1819            ok;
1820        Other1 ->
1821            ct:fail({eval, Other1, Result})
1822    end,
1823    case catch erl_eval:expr(Expr, #{}) of
1824        {'EXIT', {Result,_}} ->
1825            ok;
1826        Other2 ->
1827            ct:fail({eval, Other2, Result})
1828    end.
1829
1830error_check(String, Result, LFH, EFH) ->
1831    Exprs = parse_exprs(String),
1832    case catch erl_eval:exprs(Exprs, [], LFH, EFH) of
1833        {'EXIT', {Result,_}} ->
1834            ok;
1835        Other1 ->
1836            ct:fail({eval, Other1, Result})
1837    end,
1838    case catch erl_eval:exprs(Exprs, #{}, LFH, EFH) of
1839        {'EXIT', {Result,_}} ->
1840            ok;
1841        Other2 ->
1842            ct:fail({eval, Other2, Result})
1843    end.
1844
1845backtrace_check(String, Result, Backtrace) ->
1846    case catch parse_and_run(String) of
1847        {'EXIT', {Result, BT}} ->
1848            check_backtrace(Backtrace, remove_error_info(BT));
1849        Other ->
1850            ct:fail({eval, Other, Result})
1851    end.
1852
1853backtrace_check(String, Result, Backtrace, LFH, EFH) ->
1854    case catch parse_and_run(String, LFH, EFH) of
1855        {'EXIT', {Result, BT}} ->
1856            check_backtrace(Backtrace, remove_error_info(BT));
1857        Other ->
1858            ct:fail({eval, Other, Result})
1859    end.
1860
1861remove_error_info([{M, F, As, Info} | T]) ->
1862    [{M, F, As, lists:keydelete(error_info, 1, Info)} | T].
1863
1864backtrace_catch(String, Result, Backtrace) ->
1865    case parse_and_run(String) of
1866        {value, {'EXIT', {Result, BT}}, _Bindings} ->
1867            check_backtrace(Backtrace, remove_error_info(BT));
1868        Other ->
1869            ct:fail({eval, Other, Result})
1870    end.
1871
1872check_backtrace([B1|Backtrace], [B2|BT]) ->
1873    case {B1, B2} of
1874        {M, {M,_,_,_}} ->
1875            ok;
1876        {{M,F,A}, {M,F,A,_}} ->
1877            ok;
1878        {B, B} ->
1879            ok
1880    end,
1881    check_backtrace(Backtrace, BT);
1882check_backtrace([], _) ->
1883    ok.
1884
1885eval_string(String) ->
1886    {value, Result, _} = parse_and_run(String),
1887    Result.
1888
1889parse_expr(String) ->
1890    {ok,Tokens,_} = erl_scan:string(String),
1891    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
1892    Expr.
1893
1894parse_exprs(String) ->
1895    {ok,Tokens,_} = erl_scan:string(String),
1896    {ok, Exprs} = erl_parse:parse_exprs(Tokens),
1897    Exprs.
1898
1899parse_and_run(String) ->
1900    erl_eval:expr(parse_expr(String), []).
1901
1902parse_and_run(String, LFH, EFH) ->
1903    erl_eval:exprs(parse_exprs(String), [], LFH, EFH).
1904
1905no_final_dot(S) ->
1906    case lists:reverse(S) of
1907        " ." ++ R -> lists:reverse(R);
1908        "." ++ R -> lists:reverse(R);
1909        _ -> S
1910    end.
1911