1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2004-2019. 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(shell_SUITE).
21-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
22	 init_per_group/2,end_per_group/2]).
23
24-export([forget/1, records/1, known_bugs/1, otp_5226/1, otp_5327/1,
25	 otp_5435/1, otp_5195/1, otp_5915/1, otp_5916/1,
26	 bs_match_misc_SUITE/1, bs_match_int_SUITE/1,
27	 bs_match_tail_SUITE/1, bs_match_bin_SUITE/1,
28	 bs_construct_SUITE/1,
29	 refman_bit_syntax/1,
30	 progex_bit_syntax/1, progex_records/1,
31	 progex_lc/1, progex_funs/1,
32	 otp_5990/1, otp_6166/1, otp_6554/1,
33	 otp_7184/1, otp_7232/1, otp_8393/1, otp_10302/1, otp_13719/1,
34         otp_14285/1, otp_14296/1, typed_records/1]).
35
36-export([ start_restricted_from_shell/1,
37	  start_restricted_on_command_line/1,restricted_local/1]).
38
39%% Internal export.
40-export([otp_5435_2/0, prompt1/1, prompt2/1, prompt3/1, prompt4/1,
41	 prompt5/1]).
42
43%%
44%% Define to run outside of test server
45%%
46%% -define(STANDALONE,1).
47
48-ifdef(STANDALONE).
49-define(config(A,B),config(A,B)).
50-define(t,test_server).
51-export([config/2]).
52-define(line, noop, ).
53config(priv_dir,_) ->
54    ".".
55-else.
56-include_lib("common_test/include/ct.hrl").
57-export([init_per_testcase/2, end_per_testcase/2]).
58init_per_testcase(_Case, Config) ->
59    OrigPath = code:get_path(),
60    code:add_patha(proplists:get_value(priv_dir,Config)),
61    [{orig_path,OrigPath} | Config].
62
63end_per_testcase(_Case, Config) ->
64    OrigPath = proplists:get_value(orig_path,Config),
65    code:set_path(OrigPath),
66    application:unset_env(stdlib, restricted_shell),
67    (catch code:purge(user_default)),
68    (catch code:delete(user_default)),
69    ok.
70-endif.
71
72suite() ->
73    [{ct_hooks,[ts_install_cth]},
74     {timetrap,{minutes,10}}].
75
76all() ->
77    [forget, known_bugs, otp_5226, otp_5327,
78     otp_5435, otp_5195, otp_5915, otp_5916, {group, bits},
79     {group, refman}, {group, progex}, {group, tickets},
80     {group, restricted}, {group, records}].
81
82groups() ->
83    [{restricted, [],
84      [start_restricted_from_shell,
85       start_restricted_on_command_line, restricted_local]},
86     {bits, [],
87      [bs_match_misc_SUITE, bs_match_tail_SUITE,
88       bs_match_bin_SUITE, bs_construct_SUITE]},
89     {records, [],
90      [records, typed_records]},
91     {refman, [], [refman_bit_syntax]},
92     {progex, [],
93      [progex_bit_syntax, progex_records, progex_lc,
94       progex_funs]},
95     {tickets, [],
96      [otp_5990, otp_6166, otp_6554, otp_7184,
97       otp_7232, otp_8393, otp_10302, otp_13719, otp_14285, otp_14296]}].
98
99init_per_suite(Config) ->
100    Config.
101
102end_per_suite(_Config) ->
103    ok.
104
105init_per_group(_GroupName, Config) ->
106    Config.
107
108end_per_group(_GroupName, Config) ->
109    Config.
110
111
112-record(state, {bin, reply, leader, unic = latin1}).
113
114
115%% Test that a restricted shell can be started from the normal shell.
116start_restricted_from_shell(Config) when is_list(Config) ->
117    [{error,nofile}] = scan(<<"begin shell:start_restricted("
118			      "nonexisting_module) end.">>),
119    Test = filename:join(proplists:get_value(priv_dir, Config),
120			 "test_restricted.erl"),
121    Contents = <<"-module(test_restricted).
122                  -export([local_allowed/3, non_local_allowed/3]).
123local_allowed(m,[],State) ->
124    {true,State};
125local_allowed(ugly,[],_State) ->
126    non_conforming_reply;
127local_allowed(_,_,State) ->
128    {false,State}.
129
130non_local_allowed({shell,stop_restricted},[],State) ->
131    {true,State};
132non_local_allowed({erlang,'+'},[_],State) ->
133    {true,State};
134non_local_allowed({erlang,'-'},[_,_],_State) ->
135    non_conforming_reply;
136non_local_allowed({h, d}, [Arg], S) ->
137    {{redirect, {erlang,hd}, [Arg]}, S};
138non_local_allowed(_,_,State) ->
139    {false,State}.
140">>,
141    ok = compile_file(Config, Test, Contents, []),
142"exception exit: restricted shell starts now" =
143comm_err(<<"begin shell:start_restricted("
144	   "test_restricted) end.">>),
145{ok, test_restricted} =
146application:get_env(stdlib, restricted_shell),
147"Module" ++ _ = t({<<"begin m() end.">>, utf8}),
148"exception exit: restricted shell does not allow c(foo)" =
149comm_err(<<"begin c(foo) end.">>),
150"exception exit: restricted shell does not allow init:stop()" =
151comm_err(<<"begin init:stop() end.">>),
152"exception exit: restricted shell does not allow init:stop()" =
153comm_err(<<"begin F = fun() -> init:stop() end, F() end.">>),
154"exception error: an error occurred when evaluating an arithmetic expression" =
155comm_err(<<"begin +a end.">>),
156"exception exit: restricted shell does not allow a + b" =
157comm_err(<<"begin a+b end.">>),
158"exception exit: restricted shell does not allow - b" =
159comm_err(<<"begin -b end.">>),
160"exception exit: restricted shell does not allow 1 + 2" =
161comm_err(<<"begin if atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
162"exception exit: restricted shell does not allow 1 + 2" =
163comm_err(<<"begin if is_atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
164"exception exit: restricted shell does not allow - 2" =
165comm_err(<<"begin if - 2 -> 1; true -> 2 end end.">>),
166"exception exit: restricted shell does not allow - 2" =
167comm_err(<<"begin if (- 2 > 0)  andalso true -> 1; true -> 2 end end.">>),
168"exception exit: restricted shell does not allow - 2" =
169comm_err(<<"begin if (- 2 > 0)  orelse true -> 1; true -> 2 end end.">>),
170"exception exit: restricted shell does not allow 1 + 2" =
171comm_err(<<"begin if 1 + 2 > 0 -> 1; true -> 2 end end.">>),
172"exception exit: restricted shell does not allow 1 + 2" =
173comm_err(<<"begin if erlang:is_atom(1 + 2> 0) -> 1; true -> 2 end end.">>),
174"exception exit: restricted shell does not allow is_integer(1)" =
175comm_err(<<"begin if is_integer(1) -> 1; true -> 2 end end.">>),
176"exception exit: restricted shell does not allow is_integer(1)" =
177comm_err(<<"begin if integer(1) -> 1; true -> 2 end end.">>),
178"exception exit: "
179"restricted shell module returned bad value non_conforming_reply" =
180comm_err(<<"ugly().">>),
181[one] = scan(<<"h:d([one,two]).">>),
182"exception exit: "
183"restricted shell module returned bad value non_conforming_reply" =
184comm_err(<<"1 - 2.">>),
185"exception exit: restricted shell stopped"=
186comm_err(<<"begin shell:stop_restricted() end.">>),
187undefined =
188application:get_env(stdlib, restricted_shell),
189ok.
190
191%% Check restricted shell when started from the command line.
192start_restricted_on_command_line(Config) when is_list(Config) ->
193    {ok,Node} = start_node(shell_suite_helper_1,
194			   "-pa "++proplists:get_value(priv_dir,Config)++
195			       " -stdlib restricted_shell foo"),
196    "Warning! Restricted shell module foo not found: nofile"++_ =
197	t({Node, <<"begin m() end.">>}),
198    "exception exit: restricted shell does not allow m()" =
199	comm_err({Node, <<"begin m() end.">>}),
200    [ok] =
201	(catch scan({Node, <<"begin q() end.">>})),
202    test_server:stop_node(Node),
203    Test = filename:join(proplists:get_value(priv_dir, Config),
204			       "test_restricted2.erl"),
205    Contents = <<"-module(test_restricted2).
206                  -export([local_allowed/3, non_local_allowed/3]).
207                  local_allowed(m,[],State) ->
208                      {true,State};
209                  local_allowed(_,_,State) ->
210                      {false,State}.
211
212                  non_local_allowed({shell,stop_restricted},[],State) ->
213                      {true,State};
214                  non_local_allowed({erlang,node},[],State) ->
215                      {true,State};
216                  non_local_allowed(_,_,State) ->
217                      {false,State}.
218                 ">>,
219    ok = compile_file(Config, Test, Contents, []),
220    {ok,Node2} = start_node(shell_suite_helper_2,
221				 "-pa "++proplists:get_value(priv_dir,Config)++
222				 " -stdlib restricted_shell test_restricted2"),
223    "Module" ++ _ = t({Node2,<<"begin m() end.">>, utf8}),
224    "exception exit: restricted shell does not allow c(foo)" =
225	comm_err({Node2,<<"begin c(foo) end.">>}),
226    "exception exit: restricted shell does not allow init:stop()" =
227	comm_err({Node2,<<"begin init:stop() end.">>}),
228    "exception exit: restricted shell does not allow init:stop()" =
229	comm_err({Node2,<<"begin F = fun() -> init:stop() end, F() end.">>}),
230    [Node2] =
231	scan({Node2, <<"begin erlang:node() end.">>}),
232    [Node2] =
233	scan({Node2, <<"begin node() end.">>}),
234    "exception exit: restricted shell stopped"=
235	comm_err({Node2,<<"begin shell:stop_restricted() end.">>}),
236    [ok] =
237	scan({Node2, <<"begin q() end.">>}),
238    test_server:stop_node(Node2),
239    ok.
240
241%% Tests calling local shell functions with spectacular arguments in
242%% restricted shell.
243restricted_local(Config) when is_list(Config) ->
244    [{error,nofile}] = scan(<<"begin shell:start_restricted("
245				    "nonexisting_module) end.">>),
246    Test = filename:join(proplists:get_value(priv_dir, Config),
247			       "test_restricted_local.erl"),
248    Contents = <<"-module(test_restricted_local).
249                  -export([local_allowed/3, non_local_allowed/3]).
250                  local_allowed(m,[],State) ->
251                      {true,State};
252                  local_allowed(banan,_,State) ->
253                      {true,State};
254                  local_allowed(funkis,_,State) ->
255                      {true,State};
256                  local_allowed(c,_,State) ->
257                      {true,State};
258                  local_allowed(_,_,State) ->
259                      {false,State}.
260
261                  non_local_allowed({shell,stop_restricted},[],State) ->
262                      {true,State};
263                  non_local_allowed(_,_,State) ->
264                      {false,State}.
265                 ">>,
266    ok = compile_file(Config, Test, Contents, []),
267    Test2 = filename:join(proplists:get_value(priv_dir, Config),
268			       "user_default.erl"),
269    Contents2 = <<"-module(user_default).
270                  -export([funkis/1,apple/1]).
271                  funkis(F) when is_function(F) ->
272                      funkis;
273                  funkis(_) ->
274                      nofunkis.
275                  apple(_) ->
276                      apple.
277                 ">>,
278    ok = compile_file(Config, Test2, Contents2, []),
279    "exception exit: restricted shell starts now" =
280	comm_err(<<"begin shell:start_restricted("
281			 "test_restricted_local) end.">>),
282    {ok, test_restricted_local} =
283	application:get_env(stdlib, restricted_shell),
284    "exception exit: restricted shell does not allow foo(" ++ _ =
285	comm_err(<<"begin F=fun() -> hello end, foo(F) end.">>),
286    "exception error: undefined shell command banan/1" =
287	comm_err(<<"begin F=fun() -> hello end, banan(F) end.">>),
288    "Recompiling "++_ = t(<<"c(shell_SUITE).">>),
289    "exception exit: restricted shell does not allow l(" ++ _ =
290	comm_err(<<"begin F=fun() -> hello end, l(F) end.">>),
291    "exception error: variable 'F' is unbound" =
292	comm_err(<<"begin F=fun() -> hello end, f(F), F end.">>),
293    [funkis] =
294	scan(<<"begin F=fun() -> hello end, funkis(F) end.">>),
295    "exception exit: restricted shell does not allow apple(" ++ _ =
296	comm_err(<<"begin F=fun() -> hello end, apple(F) end.">>),
297    "exception exit: restricted shell stopped"=
298	comm_err(<<"begin shell:stop_restricted() end.">>),
299    undefined =
300	application:get_env(stdlib, restricted_shell),
301    (catch code:purge(user_default)),
302    true = (catch code:delete(user_default)),
303    ok.
304
305
306%% f/0 and f/1.
307forget(Config) when is_list(Config) ->
308    %% f/0
309    [ok] = scan(<<"begin f() end.">>),
310    "1: variable 'A' is unbound" =
311        comm_err(<<"A = 3, f(), A.">>),
312    [ok] = scan(<<"A = 3, A = f(), A.">>),
313
314    %% f/1
315    [ok] = scan(<<"begin f(A) end.">>),
316    "1: variable 'A' is unbound" =
317        comm_err(<<"A = 3, f(A), A.">>),
318    [ok] = scan(<<"A = 3, A = f(A), A.">>),
319    "exception error: no function clause matching call to f/1" =
320        comm_err(<<"f(a).">>),
321    ok.
322
323%% Test of the record support. OTP-5063.
324records(Config) when is_list(Config) ->
325    %% rd/2
326    [{attribute,_,record,{bar,_}},ok] =
327        scan(<<"rd(foo,{bar}),
328                rd(bar,{foo = (#foo{})#foo.bar}),
329                rl(bar).">>),
330    "variable 'R' is unbound" = % used to work (before OTP-5878, R11B)
331        exit_string(<<"rd(foo,{bar}),
332                       R = #foo{},
333                       rd(bar,{foo = R#foo.bar}).">>),
334    "exception error: no function clause matching call to rd/2" =
335        comm_err(<<"rd({foo},{bar}).">>),
336    "bad record declaration" = exit_string(<<"A = bar, rd(foo,A).">>),
337    [foo] = scan(<<"begin rd(foo,{bar}) end.">>),
338    "1: record foo undefined" =
339         comm_err(<<"begin rd(foo,{bar}), #foo{} end.">>),
340    ['f o o'] = scan(<<"rd('f o o', {bar}).">>),
341    [foo] = scan(<<"rd(foo,{bar}), rd(foo,{foo = #foo{}}).">>),
342
343    %% rf/0,1
344    [_, {attribute,_,record,{foo,_}},ok] =
345         scan(<<"rf('_'). rd(foo,{bar}),rl().">>),
346    "1: record foo undefined" =
347        comm_err(<<"rd(foo,{bar}), #foo{}, rf(foo), #foo{}.">>),
348    [ok,{foo,undefined}] =
349        scan(<<"rd(foo,{bar}), A = #foo{}, rf(foo). A.">>),
350    [_] = scan(<<"begin rf() end.">>),
351    [ok] = scan(<<"begin rf(foo) end.">>),
352
353    %% rp/1
354    "#foo{bar = undefined}.\nok.\n" =
355        t(<<"rd(foo,{bar}), rp(#foo{}).">>),
356    [{foo,3,4,3},ok] = scan(<<"rd(foo,{a = 3, b}), rp({foo,3,4,3}).">>),
357    "#foo{a = 12}.\nok.\n" = t(<<"rd(foo,{a = 3}), rp({foo,12}).">>),
358    [{[{foo}],12},ok] = scan(<<"rd(foo,{a = 3}), rp({[{foo}],12}).">>),
359
360    %% rr/1,2,3
361    MS = ?MODULE_STRING,
362    RR1 = "rr(" ++ MS ++ "). #state{}.",
363    "[state]\n"
364          "#state{bin = undefined,reply = undefined,leader = undefined,\n"
365          "       unic = latin1}.\n" =
366        t(RR1),
367    RR2 = "rr(" ++ MS ++ ",[state]). #state{}.",
368    "[state]\n"
369          "#state{bin = undefined,reply = undefined,leader = undefined,\n"
370          "       unic = latin1}.\n" =
371        t(RR2),
372    RR3 = "rr(" ++ MS ++ ",'_'). #state{}.",
373    "[state]\n"
374          "#state{bin = undefined,reply = undefined,leader = undefined,\n"
375          "       unic = latin1}.\n" =
376        t(RR3),
377    RR4 = "rr(" ++ MS ++ ", '_', {d,test1}).",
378    [[state]] = scan(RR4),
379
380    Test = filename:join(proplists:get_value(priv_dir, Config), "test.erl"),
381    BeamDir = filename:join(proplists:get_value(priv_dir, Config), "beam"),
382    BeamFile = filename:join(BeamDir, "test"),
383    ok = file:make_dir(BeamDir),
384    Contents = <<"-module(test).
385                  -record(state, {bin :: binary(),
386                                  reply = no,
387                                  leader = some :: atom()}).
388
389                  -ifdef(test1).
390                  -record(test1, {f}).
391                  -endif.
392
393                  -ifdef(test2).
394                  -record(test2, {g}).
395                  -endif.
396                 ">>,
397    ok = file:write_file(Test, Contents),
398    {ok, test} = compile:file(Test, [{outdir, BeamDir}]),
399
400    RR5 = "rr(\"" ++ Test ++ "\", '_', {d,test1}), rl([test1,test2]).",
401    A1 = erl_anno:new(1),
402    [{attribute,A1,record,{test1,_}},ok] = scan(RR5),
403    RR6 = "rr(\"" ++ Test ++ "\", '_', {d,test2}), rl([test1,test2]).",
404    [{attribute,A1,record,{test2,_}},ok] = scan(RR6),
405    RR7 = "rr(\"" ++ Test ++
406           "\", '_', [{d,test1},{d,test2,17}]), rl([test1,test2]).",
407    [{attribute,A1,record,{test1,_}},{attribute,A1,record,{test2,_}},ok] =
408        scan(RR7),
409    PreReply = scan(<<"rr(prim_file).">>), % preloaded...
410    true = is_list(PreReply),
411    Dir = filename:join(proplists:get_value(priv_dir, Config), "*.erl"),
412    RR8 = "rp(rr(\"" ++ Dir ++ "\")).",
413    [_,ok] = scan(RR8),
414
415    {module, test} = code:load_abs(BeamFile),
416    [[state]] = scan(<<"rr(test).">>),
417    file:delete(Test),
418    file:delete(BeamFile++".beam"),
419
420    RR1000 = "begin rr(" ++ MS ++ ") end.",
421    [_] = scan(RR1000),
422    RR1001 = "begin rr(" ++ MS ++ ", state) end.",
423    [_] = scan(RR1001),
424    RR1002 = "begin rr(" ++ MS ++ ", state,{i,'.'}) end.",
425    [_] = scan(RR1002),
426
427    [{error,nofile}] = scan(<<"rr(not_a_module).">>),
428    [{error,invalid_filename}] = scan(<<"rr({foo}).">>),
429    [[]] = scan(<<"rr(\"not_a_file\").">>),
430
431    %% using records
432    [2] = scan(<<"rd(foo,{bar}), record_info(size, foo).">>),
433    [true] = scan(<<"rd(foo,{bar}), is_record(#foo{}, foo).">>),
434    [true] = scan(<<"rd(foo,{bar}), erlang:is_record(#foo{}, foo).">>),
435    [true] = scan(<<"rd(foo,{bar}),
436                     fun() when record(#foo{},foo) -> true end().">>),
437    [2] = scan(<<"rd(foo,{bar}), #foo.bar.">>),
438    "#foo{bar = 17}.\n" =
439        t(<<"rd(foo,{bar}), A = #foo{}, A#foo{bar = 17}.">>),
440
441    %% test of is_record/2 in lc
442    "[#foo{bar = 3}].\n" =
443        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
444            "is_record(X, foo)].">>),
445    "[x,[],{a,b}].\n" =
446        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
447            "not is_record(X, foo)].">>),
448    "[#foo{bar = 3}].\n" =
449        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
450            "begin is_record(X, foo) end].">>),
451    "[x,[],{a,b}].\n" =
452        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
453            "begin not is_record(X, foo) end].">>),
454
455    "[#foo{bar = 3},x,[],{a,b}].\n" =
456        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
457            "is_record(X, foo) or not is_binary(X)].">>),
458    "[#foo{bar = 3},x,[],{a,b}].\n" =
459        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
460            "not is_record(X, foo) or not is_binary(X)].">>),
461    "[#foo{bar = 3}].\n" =
462        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
463            "is_record(X, foo) or is_reference(X)].">>),
464    "[x,[],{a,b}].\n" =
465        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
466            "not is_record(X, foo) or is_reference(X)].">>),
467
468    "[#foo{bar = 3},x,[],{a,b}].\n" =
469        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
470            "begin is_record(X, foo) or not is_binary(X) end].">>),
471    "[#foo{bar = 3},x,[],{a,b}].\n" =
472        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
473            "begin not is_record(X, foo) or not is_binary(X) end].">>),
474    "[#foo{bar = 3}].\n" =
475        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
476            "begin is_record(X, foo) or is_reference(X) end].">>),
477    "[x,[],{a,b}].\n" =
478        t(<<"rd(foo,{bar}), [X || X <- [#foo{bar=3},x,[],{a,b}],"
479            "begin not is_record(X, foo) or is_reference(X) end].">>),
480
481    [ok] =
482        scan(<<"rd(a,{}), is_record({a},a) andalso true, b().">>),
483
484    %% nested record defs
485    "#b{a = #a{}}.\n" = t(<<"rd(a,{}), rd(b, {a = #a{}}), #b{}.">>),
486
487    [ok,ok,ok] = scan(<<"rf('_'), rp(rp(rl(rf(rf(rf(rl())))))).">>),
488
489    ok.
490
491%% Test of typed record support.
492typed_records(Config) when is_list(Config) ->
493    Test = filename:join(proplists:get_value(priv_dir, Config), "test.hrl"),
494    Contents = <<"-module(test).
495                  -record(r0,{f :: any()}).
496                  -record(r1,{f1 :: #r1{} | undefined, f2 :: #r0{} | atom()}).
497                  -record(r2,{f :: #r2{} | undefined}).
498                 ">>,
499    ok = file:write_file(Test, Contents),
500
501    RR1 = "rr(\"" ++ Test ++ "\"),
502          #r1{} = (#r1{f1=#r1{f1=undefined, f2=x}, f2 = #r0{}})#r1.f1,
503          ok.",
504    RR2 = "rr(\"" ++ Test ++ "\"),
505          #r0{} = (#r1{f1=#r1{f1=undefined, f2=x}, f2 = #r0{}})#r1.f2,
506          ok. ",
507    RR3 = "rr(\"" ++ Test ++ "\"),
508          #r1{f2=#r0{}} = (#r1{f1=#r1{f1=undefined, f2=#r0{}}, f2 = x})#r1.f1,
509          ok.",
510    RR4 = "rr(\"" ++ Test ++ "\"),
511          (#r1{f2 = #r0{}})#r1{f2 = x},
512          ok. ",
513    RR5 = "rr(\"" ++ Test ++ "\"),
514          (#r1{f2 = #r0{}})#r1{f1 = #r1{}},
515          ok. ",
516    RR6 = "rr(\"" ++ Test ++ "\"),
517           (#r2{f=#r2{f=undefined}})#r2.f,
518          ok.",
519    RR7 = "rr(\"" ++ Test ++ "\"),
520           #r2{} = (#r2{f=#r2{f=undefined}})#r2.f,
521          ok.",
522    [ok] = scan(RR1),
523    [ok] = scan(RR2),
524    [ok] = scan(RR3),
525    [ok] = scan(RR4),
526    [ok] = scan(RR5),
527    [ok] = scan(RR6),
528    [ok] = scan(RR7),
529
530    file:delete(Test),
531    ok.
532
533%% Known bugs.
534known_bugs(Config) when is_list(Config) ->
535    %% erl_eval:merge_bindings/2 cannot handle _removal_ of bindings.
536    [3] = scan(<<"A = 3, length(begin f(A), [3] end), A.">>),
537    ok.
538
539%% OTP-5226. Wildcards accepted when reading BEAM files using rr/1,2,3.
540otp_5226(Config) when is_list(Config) ->
541    Test1 = <<"-module(test1).
542               -record('_test1', {a,b}).">>,
543    Test2 = <<"-module(test2).
544               -record('_test2', {c,d}).">>,
545    File1 = filename("test1.erl", Config),
546	      File2 = filename("test2.erl", Config),
547	      Beam = filename("*.beam", Config),
548	      ok = compile_file(Config, File1, Test1, [no_debug_info]),
549	      ok = compile_file(Config, File2, Test2, [no_debug_info]),
550	      RR = "rr(\"" ++ Beam ++ "\").",
551	      [Recs] = scan(RR),
552	      true = lists:member('_test1', Recs),
553	      true = lists:member('_test2', Recs),
554	      file:delete(filename("test1.beam", Config)),
555	      file:delete(filename("test2.beam", Config)),
556	      file:delete(File1),
557	      file:delete(File2),
558	      ok.
559
560%% OTP-5226. Test of eval_bits, mostly.
561otp_5327(Config) when is_list(Config) ->
562    "exception error: bad argument" =
563        comm_err(<<"<<\"hej\":default>>.">>),
564    L1 = erl_anno:new(1),
565    <<"abc">> =
566        erl_parse:normalise({bin,L1,[{bin_element,L1,{string,L1,"abc"},
567                                      default,default}]}),
568    [<<"abc">>] = scan(<<"<<(<<\"abc\">>):3/binary>>.">>),
569    [<<"abc">>] = scan(<<"<<(<<\"abc\">>)/binary>>.">>),
570    "exception error: bad argument" =
571        comm_err(<<"<<(<<\"abc\">>):4/binary>>.">>),
572    true = byte_size(hd(scan("<<3.14:64/float>>."))) =:= 8,
573    true = byte_size(hd(scan("<<3.14:32/float>>."))) =:= 4,
574    "exception error: bad argument" =
575        comm_err(<<"<<3.14:128/float>>.">>),
576    "exception error: bad argument" =
577        comm_err(<<"<<10:default>>.">>),
578    [<<98,1:1>>] = scan(<<"<<3:3,5:6>>.">>),
579    {'EXIT',{badarg,_}} =
580        (catch erl_parse:normalise({bin,L1,[{bin_element,L1,{integer,L1,17},
581                                             {atom,L1,all},
582                                             default}]})),
583    [<<-20/signed>>] = scan(<<"<<-20/signed>> = <<-20>>.">>),
584    [<<-300:16/signed>>] =
585	scan(<<"<<-300:16/signed>> = <<-300:16>>.">>),
586    [<<-1000:24/signed>>] =
587	scan(<<"<<-1000:24/signed>> = <<-1000:24>>.">>),
588    [<<-(1 bsl 29):32/signed>>] =
589        scan(<<"<<-(1 bsl 29):32/signed>> = <<-(1 bsl 29):32>>.">>),
590
591    "exception error: no match of right hand side value <<0,0,0>>" =
592        comm_err(<<"<<B:3/unit:7-binary,_/binary>> = <<0:24>>.">>),
593    true = [<<103133:64/float>>] =:=
594        scan(<<"<<103133:64/float>> = <<103133:64/float>>.">>),
595    true = [<<103133.0:64/float>>] =:=
596        scan(<<"<<103133.0:64/float>> = <<103133:64/float>>.">>),
597    true = [<<103133:64/float>>] =:= scan(<<"<<103133:64/float>>.">>),
598    Int = 17,
599    true = [<<Int:64/float>>] =:= scan(<<"Int = 17, <<Int:64/float>>.">>),
600    "exception error: no match of right hand side value" ++ _ =
601        comm_err(<<"<<103133:64/binary>> = <<103133:64/float>>.">>),
602    "exception error: interpreted function with arity 1 called with two arguments" =
603        comm_err(<<"(fun(X) -> X end)(a,b).">>),
604    {'EXIT', {{illegal_pattern,_}, _}} =
605        (catch evaluate("<<A:a>> = <<17:32>>.", [])),
606    C = <<"
607         <<A:4,B:4,C:4,D:4,E:4,F:4>> = <<\"hej\">>,
608         case <<7:4,A:4,B:4,C:4,D:4,E:4,F:4,3:4>> of
609            <<_:4,\"hej\",3:4>> -> 1;
610            _ -> 2
611         end.
612        ">>,
613    1 = evaluate(C, []),
614    %% unbound_var would be nicer...
615    {'EXIT',{{illegal_pattern,_},_}} =
616        (catch evaluate(<<"<<A:B>> = <<17:32>>.">>, [])),
617    %% undefined_bittype is turned into badmatch:
618    {'EXIT',{{badmatch,<<17:32>>},_}} =
619        (catch evaluate(<<"<<A/apa>> = <<17:32>>.">>, [])),
620    {'EXIT',_} =
621        (catch evaluate(<<"<<17/binary-unit:8-unit:16>>.">>, [])),
622    {'EXIT',_} =
623        (catch evaluate(<<"<<17:32/unsigned-signed>> = <<17:32>>.">>, [])),
624    {'EXIT',_} =
625        (catch evaluate(<<"<<17:32/unsigned-signed>>.">>, [])),
626    <<17:32>> = evaluate(<<"<<17:32/signed-signed>>.">>, []),
627    {'EXIT',_} =
628        (catch evaluate(<<"<<32/unit:8>>.">>, [])),
629    ok.
630
631%% OTP-5435. compiler application not in the path.
632otp_5435(Config) when is_list(Config) ->
633    true = <<103133:64/float>> =:=
634        evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []),
635    true = <<103133.0:64/float>> =:=
636        evaluate(<<"<<103133.0:64/float>> = <<103133:64/float>>.">>, []),
637    true = is_alive(),
638    {ok, Node} = start_node(shell_SUITE_otp_5435),
639    ok = rpc:call(Node, ?MODULE, otp_5435_2, []),
640    test_server:stop_node(Node),
641    ok.
642
643start_node(Name) ->
644    PA = filename:dirname(code:which(?MODULE)),
645    test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]).
646
647otp_5435_2() ->
648    true = code:del_path(compiler),
649    %% Make sure record evaluation is not dependent on the compiler
650    %% application being in the path.
651    %% OTP-5876.
652    [{attribute,_,record,{bar,_}},ok] =
653        scan(<<"rd(foo,{bar}),
654                rd(bar,{foo = (#foo{})#foo.bar}),
655	       rl(bar).">>),
656    ok.
657
658%% OTP-5195. QLC, mostly.
659otp_5195(Config) when is_list(Config) ->
660    %% QLC. It was easier to put these cases here than in qlc_SUITE.
661    "[#a{b = undefined}].\n" =
662        t(<<"rd(a,{b}), qlc:e(qlc:q([X || X <- [#a{}],is_record(X, a)])).">>),
663
664    %% An experimental shell used to translate error tuples:
665    %% "(qlc) \"1: generated variable 'X' must not be used in "
666    %% "list expression\".\n" =
667    %%    t(<<"qlc:q([X || X <- [{a}], Y <- [X]]).">>),
668    %% Same as last one (if the shell does not translate error tuples):
669    [{error,qlc,{1,qlc,{used_generator_variable,'X'}}}] =
670        scan(<<"qlc:q([X || X <- [{a}], Y <- [X]]).">>),
671    {error,qlc,{1,qlc,{used_generator_variable,'X'}}} =
672        evaluate(<<"qlc:q([X || X <- [{a}], Y <- [X]]).">>, []),
673    Ugly = <<"qlc:e(qlc:q([X || X <- qlc:append([[1,2,3],ugly()])])).">>,
674    "undefined shell command ugly/0" = error_string(Ugly),
675    {'EXIT',{undef,_}} = (catch evaluate(Ugly, [])),
676
677    V_1 = <<"qlc:e(qlc:q([X || X <- qlc:append([[1,2,3],v(-1)])])).">>,
678    "- 1: command not found" = comm_err(V_1),
679    {'EXIT', {undef,_}} = (catch evaluate(V_1, [])),
680
681    "1\n2\n3\n3.\n" =
682        t(<<"1. 2. 3. 3 = fun(A) when A =:= 2 -> v(3) end(v(2)).">>),
683
684    List4 = t(<<"[a,list]. A = [1,2]. "
685		"qlc:q([X || X <- qlc:append(A, v(1))]). "
686		"[1,2,a,list] = qlc:e(v(-1)).">>),
687    "[1,2,a,list].\n" = string:substr(List4, string:len(List4)-13),
688
689    ok.
690
691%% OTP-5915. Strict record tests in guards.
692otp_5915(Config) when is_list(Config) ->
693    C = <<"
694        rd(r, {a = 4,b}),
695	  rd(r1, {a,b}),
696	  rd(r2, {a = #r1{},b,c=length([1,2,3])}),
697	  rd(r3, {a = fun(_) -> #r1{} end(1), b}),
698
699	  foo = fun(A) when A#r1.a > A#r1.b -> foo end(#r1{b = 2}),
700	  0 = fun(A) when A#r2.a -> 0 end(#r2{a = true}),
701	  1 = fun(A) when (#r1{a = A})#r1.a > 2 -> 1 end(3),
702	  2 = fun(N) when ((#r2{a = #r{a = 4}, b = length([a,b,c])})#r2.a)#r.a > N ->
703		      2 end(2),
704	  3 = fun(A) when (A#r2.a)#r1.a =:= 3 -> 3 end(#r2{a = #r1{a = 3}}),
705	  ok = fun() ->
706		       F = fun(A) when record(A#r.a, r1) -> 4;
707			      (A) when record(A#r1.a, r1) -> 5
708			   end,
709		       5 = F(#r1{a = #r1{}}),
710		       4 = F(#r{a = #r1{}}),
711		       ok
712	       end(),
713	  3 = fun(A) when record(A#r1.a, r),
714			  (A#r1.a)#r.a > 3 -> 3
715	      end(#r1{a = #r{a = 4}}),
716	  7 = fun(A) when record(A#r3.a, r1) -> 7 end(#r3{}),
717	  [#r1{a = 2,b = 1}] =
718	  fun() ->
719		  [A || A <- [#r1{a = 1, b = 3},
720			      #r2{a = 2,b = 1},
721			      #r1{a = 2, b = 1}],
722			A#r1.a >
723			    A#r1.b]
724	  end(),
725	  {[_],b} =
726	  fun(L) ->
727                    %% A is checked only once:
728		  R1 = [{A,B} || A <- L, A#r1.a, B <- L, A#r1.b],
729		  A = #r2{a = true},
730                    %% A is checked again:
731		  B = if A#r1.a -> a; true -> b end,
732		  {R1,B}
733	  end([#r1{a = true, b = true}]),
734
735	  p = fun(A) when (A#r1.a =:= 2) or (A#r2.a =:= 1) -> o;
736		 (_) -> p
737	      end(#r1{a = 2}),
738
739	  o = fun(A) when (A#r1.a =:= 2) orelse (A#r2.a =:= 1) -> o;
740		 (_) -> p
741	      end(#r1{a = 2}),
742
743	  3 = fun(A) when A#r1.a > 3,
744			  record(A, r1) -> 3
745	      end(#r1{a = 5}),
746
747	  ok = fun() ->
748		       F = fun(A) when (A#r2.a =:= 1) orelse (A#r2.a) -> 2;
749			      (A) when (A#r1.a =:= 1) orelse (A#r1.a) -> 1;
750			      (A) when (A#r2.a =:= 2) andalso (A#r2.b) -> 3
751			   end,
752		       1 = F(#r1{a = 1}),
753		       2 = F(#r2{a = true}),
754		       3 = F(#r2{a = 2, b = true}),
755		       ok
756	       end(),
757
758	  b = fun(A) when false or not (A#r.a =:= 1) -> a;
759		 (_) -> b
760	      end(#r1{a = 1}),
761	  b = fun(A) when not (A#r.a =:= 1) or false -> a;
762		 (_) -> b
763	      end(#r1{a = 1}),
764
765	  ok = fun() ->
766		       F = fun(A) when not (A#r.a =:= 1) -> yes;
767			      (_) -> no
768			   end,
769		       no = F(#r1{a = 2}),
770		       yes = F(#r{a = 2}),
771		       no = F(#r{a = 1}),
772		       ok
773	       end(),
774
775	  a = fun(A) when record(A, r),
776			  A#r.a =:= 1,
777			  A#r.b =:= 2 ->a
778	      end(#r{a = 1, b = 2}),
779	  a = fun(A) when erlang:is_record(A, r),
780			  A#r.a =:= 1,
781			  A#r.b =:= 2 -> a
782	      end(#r{a = 1, b = 2}),
783	  a = fun(A) when is_record(A, r),
784			  A#r.a =:= 1,
785			  A#r.b =:= 2 -> a
786	      end(#r{a = 1, b = 2}),
787
788	  nop = fun(A) when (is_record(A, r1) and (A#r1.a > 3)) or (A#r2.a < 1) ->
789			japp;
790		   (_) ->
791			nop
792		end(#r2{a = 0}),
793	  nop = fun(A) when (A#r1.a > 3) or (A#r2.a < 1) -> japp;
794		   (_) ->
795			nop
796		end(#r2{a = 0}),
797
798	  ok = fun() ->
799		       F = fun(A) when (A#r1.a =:= 2) or (A#r2.a =:= 1) -> o;
800			      (_) -> p
801			   end,
802		       p = F(#r2{a = 1}),
803		       p = F(#r1{a = 2}),
804		       ok
805	       end(),
806
807	  ok = fun() ->
808		       F = fun(A) when fail, A#r1.a; A#r1.a -> ab;
809			      (_) -> bu
810			   end,
811		       ab = F(#r1{a = true}),
812		       bu = F(#r2{a = true}),
813		       ok
814	       end(),
815
816	  both = fun(A) when A#r.a, A#r.b -> both
817		 end(#r{a = true, b = true}),
818
819	  ok = fun() ->
820		       F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
821					  or (B#r2.b) or (A#r1.b) -> true;
822			      (_, _) -> false
823			   end,
824		       true = F(#r1{a = false, b = false}, #r2{a = false, b = true}),
825		       false = F(#r1{a = true, b = true}, #r1{a = false, b = true}),
826		       ok
827	       end(),
828
829	  ok.">>,
830    [ok] = scan(C),
831	  ok.
832
833%% OTP-5916. erlang:is_record/3 allowed in guards.
834otp_5916(Config) when is_list(Config) ->
835    C = <<"
836        rd(r1, {a,b}),
837	  rd(r2, {a,b}),
838
839	  true = if erlang:is_record(#r1{},r1,3) -> true; true ->  false end,
840	  false = if erlang:is_record(#r2{},r1,3) -> true; true ->  false end,
841
842	  true = if is_record(#r1{},r1,3) -> true; true ->  false end,
843	  false = if is_record(#r2{},r1,3) -> true; true ->  false end,
844
845	  ok.">>,
846    [ok] = scan(C),
847	  ok.
848
849
850%% OTP-5327. Adopted from parts of emulator/test/bs_match_misc_SUITE.erl.
851bs_match_misc_SUITE(Config) when is_list(Config) ->
852    C = <<"
853      F1 = fun() -> 3.1415 end,
854
855	  FOne = fun() -> 1.0 end,
856
857	  Fcmp = fun(F1, F2) when (F1 - F2) / F2 < 0.0000001 -> ok end,
858
859	  MakeSubBin = fun(Bin0) ->
860			       Sz = size(Bin0),
861			       Bin1 = <<37,Bin0/binary,38,39>>,
862			       <<_:8,Bin:Sz/binary,_:8,_:8>> = Bin1,
863			       Bin
864		       end,
865
866	  MatchFloat =
867	  fun(Bin0, Fsz, I) ->
868		  Bin = MakeSubBin(Bin0),
869		  Bsz = size(Bin) * 8,
870		  Tsz = Bsz - Fsz - I,
871		  <<_:I,F:Fsz/float,_:Tsz>> = Bin,
872		  F
873	  end,
874
875	  TFloat = fun() ->
876			   F = F1(),
877			   G = FOne(),
878
879			   G = MatchFloat(<<63,128,0,0>>, 32, 0),
880			   G = MatchFloat(<<63,240,0,0,0,0,0,0>>, 64, 0),
881
882			   Fcmp(F, MatchFloat(<<F:32/float>>, 32, 0)),
883			   Fcmp(F, MatchFloat(<<F:64/float>>, 64, 0)),
884			   Fcmp(F, MatchFloat(<<1:1,F:32/float,127:7>>, 32, 1)),
885			   Fcmp(F, MatchFloat(<<1:1,F:64/float,127:7>>, 64, 1)),
886			   Fcmp(F, MatchFloat(<<1:13,F:32/float,127:3>>, 32, 13)),
887			   Fcmp(F, MatchFloat(<<1:13,F:64/float,127:3>>, 64, 13))
888		   end,
889	  TFloat(),
890
891	  F2 = fun() -> 2.7133 end,
892
893	  MatchFloatLittle = fun(Bin0, Fsz, I) ->
894				     Bin = MakeSubBin(Bin0),
895				     Bsz = size(Bin) * 8,
896				     Tsz = Bsz - Fsz - I,
897				     <<_:I,F:Fsz/float-little,_:Tsz>> = Bin,
898				     F
899			     end,
900
901	  LittleFloat = fun() ->
902				F = F2(),
903				G = FOne(),
904
905				G = MatchFloatLittle(<<0,0,0,0,0,0,240,63>>, 64, 0),
906				G = MatchFloatLittle(<<0,0,128,63>>, 32, 0),
907
908				Fcmp(F, MatchFloatLittle(<<F:32/float-little>>, 32, 0)),
909				Fcmp(F, MatchFloatLittle(<<F:64/float-little>>, 64, 0)),
910				Fcmp(F, MatchFloatLittle(<<1:1,F:32/float-little,127:7>>, 32, 1)),
911				Fcmp(F, MatchFloatLittle(<<1:1,F:64/float-little,127:7>>, 64, 1)),
912				Fcmp(F, MatchFloatLittle(<<1:13,F:32/float-little,127:3>>, 32, 13)),
913				Fcmp(F, MatchFloatLittle(<<1:13,F:64/float-little,127:3>>, 64, 13))
914			end,
915	  LittleFloat(),
916
917	  Sean1 = fun(<<B/binary>>) when size(B) < 4 -> small;
918		     (<<1, _B/binary>>) -> large
919		  end,
920
921	  Sean = fun() ->
922			 small = Sean1(<<>>),
923			 small = Sean1(<<1>>),
924			 small = Sean1(<<1,2>>),
925			 small = Sean1(<<1,2,3>>),
926			 large = Sean1(<<1,2,3,4>>),
927
928			 small = Sean1(<<4>>),
929			 small = Sean1(<<4,5>>),
930			 small = Sean1(<<4,5,6>>),
931			 {'EXIT',{function_clause,_}} = (catch Sean1(<<4,5,6,7>>))
932		 end,
933	  Sean(),
934
935	  NativeBig = fun() ->
936			      <<37.33:64/native-float>> = <<37.33:64/big-float>>,
937			      <<3974:16/native-integer>> = <<3974:16/big-integer>>
938		      end,
939
940	  NativeLittle = fun() ->
941				 <<37869.32343:64/native-float>> = <<37869.32343:64/little-float>>,
942				 <<7974:16/native-integer>> = <<7974:16/little-integer>>
943			 end,
944
945	  Native = fun() ->
946			   <<3.14:64/native-float>> = <<3.14:64/native-float>>,
947			   <<333:16/native>> = <<333:16/native>>,
948			   <<38658345:32/native>> = <<38658345:32/native>>,
949			   case <<1:16/native>> of
950			       <<0,1>> -> NativeBig();
951			       <<1,0>> -> NativeLittle()
952			   end
953		   end,
954	  Native(),
955
956	  Split = fun(<<N:16,B:N/binary,T/binary>>) -> {B,T} end,
957
958	  Split2 = fun(N, <<N:16,B:N/binary,T/binary>>) -> {B,T} end,
959
960	  Split_2 = fun(<<N0:8,N:N0,B:N/binary,T/binary>>) -> {B,T} end,
961
962	  Skip = fun(<<N:8,_:N/binary,T/binary>>) -> T end,
963
964	  SizeVar = fun() ->
965			    {<<45>>,<<>>} = Split(<<1:16,45>>),
966			    {<<45>>,<<46,47>>} = Split(<<1:16,45,46,47>>),
967			    {<<45,46>>,<<47>>} = Split(<<2:16,45,46,47>>),
968
969			    {<<45,46,47>>,<<48>>} = Split_2(<<16:8,3:16,45,46,47,48>>),
970
971			    {<<45,46>>,<<47>>} = Split2(2, <<2:16,45,46,47>>),
972			    {'EXIT',{function_clause,_}} =
973				(catch Split2(42, <<2:16,45,46,47>>)),
974
975			    <<\"cdef\">> = Skip(<<2:8,\"abcdef\">>)
976       end,
977			      SizeVar(),
978
979			      Wcheck = fun(<<A>>) when A==3-> ok1;
980					  (<<_,_:2/binary>>) -> ok2;
981					  (<<_>>) -> ok3;
982					  (Other) -> {error,Other}
983				       end,
984
985			      Wiger = fun()  ->
986					      ok1 = Wcheck(<<3>>),
987					      ok2 = Wcheck(<<1,2,3>>),
988					      ok3 = Wcheck(<<4>>),
989					      {error,<<1,2,3,4>>} = Wcheck(<<1,2,3,4>>),
990					      {error,<<>>} = Wcheck(<<>>)
991				      end,
992			      Wiger(),
993
994			      ok.
995">>,
996    [ok] = scan(C),
997ok = evaluate(C, []).
998
999%% This one is not run during night builds since it takes several minutes.
1000
1001%% OTP-5327. Adopted from emulator/test/bs_match_int_SUITE.erl.
1002bs_match_int_SUITE(Config) when is_list(Config) ->
1003    C = <<"
1004       FunClause = fun({'EXIT',{function_clause,_}}) -> ok end,
1005
1006	  Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
1007
1008	  GetInt1 = fun(<<I:0>>) -> I;
1009		       (<<I:8>>) -> I;
1010		       (<<I:16>>) -> I;
1011		       (<<I:24>>) -> I;
1012		       (<<I:32>>) -> I
1013		    end,
1014
1015	  GetInt2 = fun(Bin0, I, F) when size(Bin0) < 4 ->
1016			    Bin = <<0,Bin0/binary>>,
1017			    I = GetInt1(Bin),
1018			    F(Bin, I, F);
1019		       (_, I, _F) -> I
1020		    end,
1021
1022	  GetInt = fun(Bin) ->
1023			   I = GetInt1(Bin),
1024			   GetInt2(Bin, I, GetInt2)
1025		   end,
1026
1027
1028	  Cmp128 = fun(<<I:128>>, I) -> equal;
1029		      (_, _) -> not_equal
1030		   end,
1031
1032	  Uint2 = fun([H|T], Acc, F) -> F(T, Acc bsl 8 bor H, F);
1033		     ([], Acc, _F) -> Acc
1034		  end,
1035
1036	  Uint = fun(L) -> Uint2(L, 0, Uint2) end,
1037
1038	  Integer = fun() ->
1039			    0 = GetInt(Mkbin([])),
1040			    0 = GetInt(Mkbin([0])),
1041			    42 = GetInt(Mkbin([42])),
1042			    255 = GetInt(Mkbin([255])),
1043			    256 = GetInt(Mkbin([1,0])),
1044			    257 = GetInt(Mkbin([1,1])),
1045			    258 = GetInt(Mkbin([1,2])),
1046			    258 = GetInt(Mkbin([1,2])),
1047			    65534 = GetInt(Mkbin([255,254])),
1048			    16776455 = GetInt(Mkbin([255,253,7])),
1049			    4245492555 = GetInt(Mkbin([253,13,19,75])),
1050			    4294967294 = GetInt(Mkbin([255,255,255,254])),
1051			    4294967295 = GetInt(Mkbin([255,255,255,255])),
1052			    Eight = [200,1,19,128,222,42,97,111],
1053			    Cmp128(Eight, Uint(Eight)),
1054			    FunClause(catch GetInt(Mkbin(lists:seq(1,5))))
1055		    end,
1056	  Integer(),
1057
1058	  Sint = fun(Bin) ->
1059			 case Bin of
1060			     <<I:8/signed>> -> I;
1061			     <<I:8/signed,_:3,_:5>> -> I;
1062			     Other -> {no_match,Other}
1063			 end
1064		 end,
1065
1066	  SignedInteger = fun() ->
1067				  {no_match,_} = Sint(Mkbin([])),
1068				  {no_match,_} = Sint(Mkbin([1,2,3])),
1069				  127 = Sint(Mkbin([127])),
1070				  -1 = Sint(Mkbin([255])),
1071				  -128 = Sint(Mkbin([128])),
1072				  42 = Sint(Mkbin([42,255])),
1073				  127 = Sint(Mkbin([127,255]))
1074			  end,
1075	  SignedInteger(),
1076
1077	  Dynamic5 = fun(Bin, S1, S2, A, B) ->
1078			     case Bin of
1079				 <<A:S1,B:S2>> ->
1080                              %% io:format(\"~p ~p ~p ~p~n\", [S1,S2,A,B]),
1081				     ok;
1082				 _Other -> erlang:error(badmatch, [Bin,S1,S2,A,B])
1083			     end
1084		     end,
1085
1086	  Dynamic2 = fun(Bin, S1, F) when S1 >= 0 ->
1087			     S2 = size(Bin) * 8 - S1,
1088			     Dynamic5(Bin, S1, S2, (1 bsl S1) - 1, (1 bsl S2) - 1),
1089			     F(Bin, S1-1, F);
1090			(_, _, _) -> ok
1091		     end,
1092
1093	  Dynamic = fun(Bin, S1) ->
1094			    Dynamic2(Bin, S1, Dynamic2)
1095		    end,
1096
1097	  Dynamic(Mkbin([255]), 8),
1098	  Dynamic(Mkbin([255,255]), 16),
1099	  Dynamic(Mkbin([255,255,255]), 24),
1100	  Dynamic(Mkbin([255,255,255,255]), 32),
1101
1102	  BigToLittle4 =
1103	  fun([B0,B1,B2,B3,B4,B5,B6,B7|T], N, Acc, F) when N >= 8 ->
1104		  F(T, N-8, [B0,B1,B2,B3,B4,B5,B6,B7|Acc], F);
1105	     (List, N, Acc, _F) -> lists:sublist(List, 1, N) ++ Acc
1106	  end,
1107
1108	  BigToLittle =
1109	  fun(List, N) -> BigToLittle4(List, N, [], BigToLittle4) end,
1110
1111	  ReversedSublist =
1112	  fun(_List, 0, Acc, _F) -> Acc;
1113	     ([H|T], N, Acc, F) -> F(T, N-1, [H|Acc], F)
1114	  end,
1115
1116	  TwoComplementAndReverse =
1117	  fun([H|T], Carry, Acc, F) ->
1118		  Sum = 1-H+Carry,
1119		  F(T, Sum div 2, [Sum rem 2|Acc], F);
1120	     ([], Carry, Acc, _F) -> [Carry|Acc]
1121	  end,
1122
1123	  MakeInt = fun(_List, 0, Acc, _F) -> Acc;
1124		       ([H|T], N, Acc, F) -> F(T, N-1, Acc bsl 1 bor H, F)
1125		    end,
1126
1127	  MakeSignedInt =
1128	  fun(_List, 0) -> 0;
1129	     ([0|_]=List, N) -> MakeInt(List, N, 0, MakeInt);
1130	     ([1|_]=List0, N) ->
1131		  List1 = ReversedSublist(List0, N, [], ReversedSublist),
1132		  List2 = TwoComplementAndReverse(List1, 1, [],
1133						  TwoComplementAndReverse),
1134		  -MakeInt(List2, length(List2), 0, MakeInt)
1135	  end,
1136
1137	  BitsToList =
1138	  fun([H|T], 0, F) -> F(T, 16#80, F);
1139	     ([H|_]=List, Mask, F) ->
1140		  [case H band Mask of
1141                       0 -> 0;
1142                       _ -> 1
1143		   end | F(List, Mask bsr 1, F)];
1144	     ([], _, _F) -> []
1145	  end,
1146
1147	  MoreDynamic3 =
1148	  fun(Action, Bin, List, Bef, Aft, F) when Bef =< Aft ->
1149		  Action(Bin, List, Bef, Aft-Bef),
1150		  F(Action, Bin, List, Bef, Aft-1, F);
1151	     (_, _, _, _, _, _) -> ok
1152	  end,
1153
1154	  MoreDynamic2 =
1155	  fun(Action, Bin, [_|T]=List, Bef, F) ->
1156		  MoreDynamic3(Action, Bin, List, Bef, size(Bin)*8,
1157			       MoreDynamic3),
1158		  F(Action, Bin, T, Bef+1, F);
1159	     (_, _, [], _, _F) -> ok
1160	  end,
1161
1162	  MoreDynamic1 =
1163	  fun(Action, Bin) ->
1164		  BitList = BitsToList(binary_to_list(Bin),16#80,BitsToList),
1165		  MoreDynamic2(Action, Bin, BitList, 0, MoreDynamic2)
1166	  end,
1167
1168	  MoreDynamic = fun() ->
1169           %% Unsigned big-endian numbers.
1170				Unsigned  = fun(Bin, List, SkipBef, N) ->
1171						    SkipAft = 8*size(Bin) - N - SkipBef,
1172						    <<_:SkipBef,Int:N,_:SkipAft>> = Bin,
1173						    Int = MakeInt(List, N, 0, MakeInt)
1174					    end,
1175				MoreDynamic1(Unsigned, erlang:md5(Mkbin([42]))),
1176
1177           %% Signed big-endian numbers.
1178				Signed  = fun(Bin, List, SkipBef, N) ->
1179						  SkipAft = 8*size(Bin) - N - SkipBef,
1180						  <<_:SkipBef,Int:N/signed,_:SkipAft>> = Bin,
1181						  case MakeSignedInt(List, N) of
1182						      Int -> ok;
1183						      Other ->
1184							  io:format(\"Bin = ~p,\", [Bin]),
1185                                     io:format(\"SkipBef = ~p, N = ~p\",
1186                                               [SkipBef,N]),
1187								    io:format(\"Expected ~p, got ~p\",
1188                                               [Int,Other])
1189								    end
1190								    end,
1191								    MoreDynamic1(Signed, erlang:md5(Mkbin([43]))),
1192
1193           %% Unsigned little-endian numbers.
1194								    UnsLittle  = fun(Bin, List, SkipBef, N) ->
1195											 SkipAft = 8*size(Bin) - N - SkipBef,
1196											 <<_:SkipBef,Int:N/little,_:SkipAft>> = Bin,
1197											 Int = MakeInt(BigToLittle(List, N), N, 0,
1198												       MakeInt)
1199										 end,
1200								    MoreDynamic1(UnsLittle, erlang:md5(Mkbin([44]))),
1201
1202           %% Signed little-endian numbers.
1203								    SignLittle  = fun(Bin, List, SkipBef, N) ->
1204											  SkipAft = 8*size(Bin) - N - SkipBef,
1205											  <<_:SkipBef,Int:N/signed-little,_:SkipAft>> = Bin,
1206											  Little = BigToLittle(List, N),
1207											  Int = MakeSignedInt(Little, N)
1208										  end,
1209								    MoreDynamic1(SignLittle, erlang:md5(Mkbin([45])))
1210								    end,
1211								    MoreDynamic(),
1212
1213								    ok.
1214">>,
1215    [ok] = scan(C),
1216ok = evaluate(C, []).
1217
1218%% OTP-5327. Adopted from emulator/test/bs_match_tail_SUITE.erl.
1219bs_match_tail_SUITE(Config) when is_list(Config) ->
1220    C = <<"
1221          GetTailUsed = fun(<<A:1,T/binary>>) -> {A,T} end,
1222
1223          GetTailUnused = fun(<<A:15,_/binary>>) -> A end,
1224
1225          GetDynTailUsed = fun(Bin, Sz) ->
1226				   <<A:Sz,T/binary>> = Bin,
1227				   {A,T}
1228                           end,
1229
1230          GetDynTailUnused = fun(Bin, Sz) ->
1231				     <<A:Sz,_/binary>> = Bin,
1232				     A
1233                             end,
1234
1235          Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
1236
1237          TestZeroTail = fun(<<A:8>>) -> A end,
1238
1239          TestZeroTail2 = fun(<<_A:4,_B:4>>) -> ok end,
1240
1241          ZeroTail = fun() ->
1242			     7 = (catch TestZeroTail(Mkbin([7]))),
1243			     {'EXIT',{function_clause,_}} =
1244				 (catch TestZeroTail(Mkbin([1,2]))),
1245			     {'EXIT',{function_clause,_}} =
1246				 (catch TestZeroTail2(Mkbin([1,2,3])))
1247		     end,
1248          ZeroTail(),
1249
1250          AlGetTailUsed = fun(<<A:16,T/binary>>) -> {A,T} end,
1251
1252          AlGetTailUnused = fun(<<A:16,_/binary>>) -> A end,
1253
1254          Aligned = fun() ->
1255			    Tail1 = Mkbin([]),
1256			    {258,Tail1} = AlGetTailUsed(Mkbin([1,2])),
1257			    Tail2 = Mkbin(lists:seq(1, 127)),
1258			    {35091,Tail2} = AlGetTailUsed(Mkbin([137,19|Tail2])),
1259
1260			    64896 = AlGetTailUnused(Mkbin([253,128])),
1261			    64895 = AlGetTailUnused(Mkbin([253,127|lists:seq(42, 255)])),
1262
1263			    Tail3 = Mkbin(lists:seq(0, 19)),
1264			    {0,Tail1} = GetDynTailUsed(Tail1, 0),
1265			    {0,Tail3} = GetDynTailUsed(Mkbin([Tail3]), 0),
1266			    {73,Tail3} = GetDynTailUsed(Mkbin([73|Tail3]), 8),
1267
1268			    0 = GetDynTailUnused(Mkbin([]), 0),
1269			    233 = GetDynTailUnused(Mkbin([233]), 8),
1270			    23 = GetDynTailUnused(Mkbin([23,22,2]), 8)
1271		    end,
1272          Aligned(),
1273
1274          UnAligned = fun() ->
1275			      {'EXIT',{function_clause,_}} =
1276				  (catch GetTailUsed(Mkbin([42]))),
1277			      {'EXIT',{{badmatch,_},_}} =
1278				  (catch GetDynTailUsed(Mkbin([137]), 3)),
1279			      {'EXIT',{function_clause,_}} =
1280				  (catch GetTailUnused(Mkbin([42,33]))),
1281			      {'EXIT',{{badmatch,_},_}} =
1282				  (catch GetDynTailUnused(Mkbin([44]), 7))
1283		      end,
1284          UnAligned(),
1285          ok.
1286">>,
1287    [ok] = scan(C),
1288ok = evaluate(C, []).
1289
1290%% OTP-5327. Adopted from emulator/test/bs_match_bin_SUITE.erl.
1291bs_match_bin_SUITE(Config) when is_list(Config) ->
1292    ByteSplitBinary =
1293        <<"ByteSplit =
1294             fun(L, B, Pos, Fun) when Pos >= 0 ->
1295                     Sz1 = Pos,
1296                     Sz2 = size(B) - Pos,
1297                     <<B1:Sz1/binary,B2:Sz2/binary>> = B,
1298                     B1 = list_to_binary(lists:sublist(L, 1, Pos)),
1299                     B2 = list_to_binary(lists:nthtail(Pos, L)),
1300		     Fun(L, B, Pos-1, Fun);
1301		(L, B, _, _Fun) -> ok
1302             end,
1303	  Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
1304	  L = lists:seq(0, 57),
1305	  B = Mkbin(L),
1306	  ByteSplit(L, B, size(B), ByteSplit),
1307	  Id = fun(I) -> I end,
1308	  MakeUnalignedSubBinary =
1309	  fun(Bin0) ->
1310		  Bin1 = <<0:3,Bin0/binary,31:5>>,
1311		  Sz = size(Bin0),
1312		  <<0:3,Bin:Sz/binary,31:5>> = Id(Bin1),
1313		  Bin
1314	  end,
1315	  Unaligned = MakeUnalignedSubBinary(B),
1316	  ByteSplit(L, Unaligned, size(Unaligned), ByteSplit),
1317	  ok.
1318">>,
1319    [ok] = scan(ByteSplitBinary),
1320ok = evaluate(ByteSplitBinary, []),
1321BitSplitBinary =
1322<<"Mkbin = fun(L) when list(L) -> list_to_binary(L) end,
1323
1324           MakeInt =
1325  fun(List, 0, Acc, _F) -> Acc;
1326     ([H|T], N, Acc, F) -> F(T, N-1, Acc bsl 1 bor H, F)
1327  end,
1328
1329  MakeBinFromList =
1330  fun(List, 0, _F) -> Mkbin([]);
1331     (List, N, F) ->
1332	  list_to_binary([MakeInt(List, 8, 0, MakeInt),
1333			  F(lists:nthtail(8, List), N-8, F)])
1334  end,
1335
1336  BitSplitBinary3 =
1337  fun(Action, Bin, List, Bef, Aft, F) when Bef =< Aft ->
1338	  Action(Bin, List, Bef, (Aft-Bef) div 8 * 8),
1339	  F(Action, Bin, List, Bef, Aft-8, F);
1340     (_, _, _, _, _, _) -> ok
1341  end,
1342
1343  BitSplitBinary2 =
1344  fun(Action, Bin, [_|T]=List, Bef, F) ->
1345	  BitSplitBinary3(Action, Bin, List, Bef, size(Bin)*8,
1346			  BitSplitBinary3),
1347	  F(Action, Bin, T, Bef+1, F);
1348     (Action, Bin, [], Bef, F) -> ok
1349  end,
1350
1351  BitsToList =
1352  fun([H|T], 0, F) -> F(T, 16#80, F);
1353     ([H|_]=List, Mask, F) ->
1354	  [case H band Mask of
1355	       0 -> 0;
1356	       _ -> 1
1357	   end | F(List, Mask bsr 1, F)];
1358     ([], _, _F) -> []
1359  end,
1360
1361  BitSplitBinary1 =
1362  fun(Action, Bin) ->
1363	  BitList = BitsToList(binary_to_list(Bin), 16#80,
1364			       BitsToList),
1365	  BitSplitBinary2(Action, Bin, BitList, 0, BitSplitBinary2)
1366  end,
1367
1368  Fun = fun(Bin, List, SkipBef, N) ->
1369		SkipAft = 8*size(Bin) - N - SkipBef,
1370		<<I1:SkipBef,OutBin:N/binary-unit:1,I2:SkipAft>> = Bin,
1371		OutBin = MakeBinFromList(List, N, MakeBinFromList)
1372	end,
1373
1374  BitSplitBinary1(Fun, erlang:md5(<<1,2,3>>)),
1375  Id = fun(I) -> I end,
1376  MakeUnalignedSubBinary =
1377  fun(Bin0) ->
1378	  Bin1 = <<0:3,Bin0/binary,31:5>>,
1379	  Sz = size(Bin0),
1380	  <<0:3,Bin:Sz/binary,31:5>> = Id(Bin1),
1381	  Bin
1382  end,
1383  BitSplitBinary1(Fun, MakeUnalignedSubBinary(erlang:md5(<<1,2,3>>))),
1384  ok.
1385">>,
1386    [ok] = scan(BitSplitBinary),
1387ok = evaluate(BitSplitBinary, []).
1388
1389-define(FAIL(Expr), "{'EXIT',{badarg,_}} = (catch " ??Expr ")").
1390
1391-define(COF(Int0),
1392        "(fun(Int) ->
1393                       true = <<Int:32/float>> =:= <<(float(Int)):32/float>>,
1394	true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
1395	    end)(Nonliteral(" ??Int0 ")),
1396true = <<" ??Int0 ":32/float>> =:= <<(float("??Int0")):32/float>>,
1397true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>").
1398
1399-define(COF64(Int0),
1400        "(fun(Int) ->
1401                       true = <<Int:64/float>> =:= <<(float(Int)):64/float>>
1402	    end)(Nonliteral(" ??Int0 ")),
1403true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>").
1404
1405%% OTP-5327. Adopted from parts of emulator/test/bs_construct_SUITE.erl.
1406bs_construct_SUITE(Config) when is_list(Config) ->
1407    C1 = <<"
1408
1409       Testf_1 = fun(W, B) -> "
1410            ?FAIL(<<42:W>>) ","
1411				  ?FAIL(<<3.14:W/float>>) ","
1412				  ?FAIL(<<B:W/binary>>) "
1413       end,
1414
1415	   TestF = fun() -> "
1416            ?FAIL(<<3.14>>) ","
1417				?FAIL(<<<<1,2>>>>) ","
1418
1419				?FAIL(<<2.71/binary>>) ","
1420				?FAIL(<<24334/binary>>) ","
1421				?FAIL(<<24334344294788947129487129487219847/binary>>) ","
1422
1423				?FAIL(<<<<1,2,3>>/float>>) ",
1424
1425            %% Negative field widths.
1426            Testf_1(-8, <<1,2,3,4,5>>),"
1427
1428            ?FAIL(<<42:(-16)>>) ","
1429				?FAIL(<<3.14:(-8)/float>>) ","
1430				?FAIL(<<<<23,56,0,2>>:(-16)/binary>>) ","
1431				?FAIL(<<<<23,56,0,2>>:(2.5)/binary>>) ","
1432				?FAIL(<<<<23,56,0,2>>:(anka)>>) "
1433       end,
1434	   TestF(),
1435
1436	   NotUsed1 = fun(I, BinString) -> <<I:32,BinString/binary>>, ok end,
1437
1438	   NotUsed2 = fun(I, Sz) -> <<I:Sz>>, ok end,
1439
1440	   NotUsed3 = fun(I) -><<I:(-8)>>, ok end,
1441
1442	   NotUsed = fun() ->
1443			     ok = NotUsed1(3, <<\"dum\">>),
1444            {'EXIT',{badarg,_}} = (catch NotUsed1(3, \"dum\")), "
1445						  ?FAIL(NotUsed2(444, -2)) ","
1446						  ?FAIL(NotUsed2(444, anka)) ","
1447						  ?FAIL(NotUsed3(444)) "
1448       end,
1449						  NotUsed(),
1450
1451						  InGuard3 = fun(Bin, A, B) when <<A:13,B:3>> == Bin -> 1;
1452								(Bin, A, B) when <<A:16,B/binary>> == Bin -> 2;
1453								(Bin, A, B) when <<A:14,B/float,3:2>> == Bin -> 3;
1454								(Bin, A, B) when {a,b,<<A:14,B/float,3:2>>} == Bin ->
1455								     cant_happen;
1456								(_, _, _) -> nope
1457							     end,
1458
1459						  InGuard = fun() ->
1460								    1 = InGuard3(<<16#74ad:16>>, 16#e95, 5),
1461								    2 = InGuard3(<<16#3A,16#F7,\"hello\">>, 16#3AF7, <<\"hello\">>),
1462            3 = InGuard3(<<16#FBCD:14,3.1415/float,3:2>>, 16#FBCD, 3.1415),
1463										   nope = InGuard3(<<1>>, 42, b),
1464										   nope = InGuard3(<<1>>, a, b),
1465										   nope = InGuard3(<<1,2>>, 1, 1),
1466										   nope = InGuard3(<<4,5>>, 1, 2.71),
1467										   nope = InGuard3(<<4,5>>, 1, <<12,13>>)
1468										   end,
1469										   InGuard(),
1470
1471										   Nonliteral = fun(X) -> X end,
1472
1473										   CoerceToFloat = fun() -> "
1474           ?COF(0) ","
1475														?COF(-1) ","
1476														?COF(1) ","
1477														?COF(42) ","
1478														?COF(255) ","
1479														?COF(-255) ","
1480														?COF64(298748888888888888888888888883478264866528467367364766666666666666663) ","
1481														?COF64(-367546729879999999999947826486652846736736476555566666663) "
1482       end,
1483										   CoerceToFloat(),
1484										   ok.
1485">>,
1486    [ok] = scan(C1),
1487ok = evaluate(C1, []),
1488
1489%% There is another one, lib/compiler/test/bs_construct_SUITE.erl...
1490C2 = <<"
1491       I = fun(X) -> X end,
1492
1493       Fail = fun() ->
1494
1495		      I_minus_777 = I(-777),
1496		      I_minus_2047 = I(-2047),
1497
1498         %% One negative field size, but the sum of field sizes will be 1 byte.
1499         %% Make sure that we reject that properly.
1500
1501		      {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8,
1502						     57:I_minus_2047/unit:8>>),
1503
1504         %% Same thing, but use literals.
1505		      {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8,
1506						     57:(-2047)/unit:8>>),
1507
1508         %% Bad alignment.
1509		      I_one = I(1),
1510		      <<1:1>> = <<2375:I_one>>,
1511		      <<3:2>> = <<45:1,2375:I_one>>,
1512		      <<14:4>> = <<45:1,2375:I_one,918:2>>,
1513		      <<118:7>> = <<45:1,2375:I_one,918:5>>,
1514
1515         %% Not numbers.
1516		      {'EXIT',{badarg,_}} = (catch <<45:(I(not_a_number))>>),
1517		      {'EXIT',{badarg,_}} = (catch <<13:8,45:(I(not_a_number))>>),
1518
1519         %% Unaligned sizes.
1520		      BadSz = I(7),
1521		      <<2:4>> = <<34:4>>,
1522		      <<34:7>> = <<34:BadSz>>,
1523
1524		      [] = [X || {X} <- [], X == <<3:BadSz>>],
1525		      [] = [X || {X} <- [], X == <<3:4>>]
1526	      end,
1527       Fail(),
1528
1529       FloatBin1 = fun(F) ->
1530			   {<<1,2,3>>,F+3.0}
1531		   end,
1532
1533       FloatBin = fun() ->
1534           %% Some more coverage.
1535			  {<<1,2,3>>,7.0} = FloatBin1(4)
1536		  end,
1537       FloatBin(),
1538
1539       ok.
1540">>,
1541    [ok] = scan(C2),
1542ok = evaluate(C2, []).
1543
1544evaluate(B, Vars) when is_binary(B) ->
1545    evaluate(binary_to_list(B), Vars);
1546evaluate(Str, Vars) ->
1547    {ok,Tokens,_} =
1548	erl_scan:string(Str),
1549    {ok, Exprs} = erl_parse:parse_exprs(Tokens),
1550    case erl_eval:exprs(Exprs, Vars, none) of
1551	{value, Result, _} ->
1552	    Result
1553    end.
1554
1555
1556%% Bit syntax examples from the Reference Manual. OTP-5237.
1557refman_bit_syntax(Config) when is_list(Config) ->
1558    %% Reference Manual "Bit Syntax Expressions"
1559    Bin1 = <<1,17,42>>,
1560    true = [1,17,42] =:= binary_to_list(Bin1),
1561    Bin2 = <<"abc">>,
1562    true = "abc" =:= binary_to_list(Bin2),
1563    Bin3 = <<1,17,42:16>>,
1564    true = [1,17,0,42] =:= binary_to_list(Bin3),
1565    <<_A,_B,C:16>> = <<1,17,42:16>>,
1566    true = C =:= 42,
1567    <<D:16,_E,F>> = <<1,17,42:16>>,
1568    true = D =:= 273,
1569    true = F =:= 42,
1570    <<_G,H/binary>> = <<1,17,42:16>>,
1571    true = H =:= <<17,0,42>>,
1572
1573    [ok] =
1574        scan(<<"Bin1 = <<1,17,42>>,
1575                         true = [1,17,42] =:= binary_to_list(Bin1),
1576	       Bin2 = <<\"abc\">>,
1577                         true = \"abc\" =:= binary_to_list(Bin2),
1578                         Bin3 = <<1,17,42:16>>,
1579			true =
1580			[1,17,0,42] =:= binary_to_list(Bin3),
1581			<<A,B,C:16>> = <<1,17,42:16>>,
1582			true = C =:= 42,
1583			<<D:16,E,F>> = <<1,17,42:16>>,
1584			true = D =:= 273,
1585			true = F =:= 42,
1586			<<G,H/binary>> = <<1,17,42:16>>,
1587			true = H =:= <<17,0,42>>,
1588			ok.">>),
1589
1590    %% Binary comprehensions.
1591    <<2,4,6>> =  << << (X*2) >> || <<X>> <= << 1,2,3 >> >>,
1592			ok.
1593
1594
1595-define(IP_VERSION, 4).
1596-define(IP_MIN_HDR_LEN, 5).
1597
1598%% Bit syntax examples from Programming Examples. OTP-5237.
1599progex_bit_syntax(Config) when is_list(Config) ->
1600    Bin11 = <<1, 17, 42>>,
1601    true = [1, 17, 42] =:= binary_to_list(Bin11),
1602    Bin12 = <<"abc">>,
1603    true = [97, 98, 99] =:= binary_to_list(Bin12),
1604
1605    A = 1, B = 17, C = 42,
1606    Bin2 = <<A, B, C:16>>,
1607    true = [1, 17, 00, 42] =:= binary_to_list(Bin2),
1608    <<D:16, E, F/binary>> = Bin2,
1609    true = D =:= 273,
1610    true = E =:= 00,
1611    true = [42] =:= binary_to_list(F),
1612
1613    Fun4 = fun(Dgram) ->
1614                   DgramSize = byte_size(Dgram),
1615                   case Dgram of
1616                       <<?IP_VERSION:4, HLen:4, SrvcType:8, TotLen:16,
1617			 ID:16, Flgs:3, FragOff:13,
1618			 TTL:8, Proto:8, HdrChkSum:16,
1619			 SrcIP:32, DestIP:32,
1620			 RestDgram/binary>> when HLen>=5, 4*HLen=<DgramSize ->
1621                           OptsLen = 4*(HLen - ?IP_MIN_HDR_LEN),
1622                           <<Opts:OptsLen/binary,Data/binary>> = RestDgram,
1623                           {SrvcType, TotLen, Flgs, FragOff, ID, HdrChkSum,
1624                            Proto, TTL, SrcIP, DestIP, Data, Opts};
1625                       _ ->
1626                           not_ok
1627                   end
1628           end,
1629    true = Fun4(<<>>) =:= not_ok,
1630    true = is_tuple(Fun4(list_to_binary([<<?IP_VERSION:4,5:4>>,
1631                                         list_to_binary(lists:seq(1,255))]))),
1632
1633    X = 23432324, Y = 24324234,
1634    <<10:7>> = <<X:1, Y:6>>,
1635    Z = 234324324,
1636    XYZ = <<X:1, Y:6, Z:1>>,
1637    true = [20] =:= binary_to_list(XYZ),
1638    Hello1 = <<"hello">>,
1639    Hello2 = <<$h,$e,$l,$l,$o>>,
1640    true = "hello" =:= binary_to_list(Hello1),
1641    true = "hello" =:= binary_to_list(Hello2),
1642
1643    FunM1 = fun(<<X1:7/binary, Y1:1/binary>>) -> {X1,Y1} end,
1644    true = {<<"1234567">>,<<"8">>} =:= FunM1(<<"12345678">>),
1645
1646    FunM2 = fun(<<_X1:7/binary-unit:7, _Y1:1/binary-unit:1>>) -> ok;
1647               (_) -> not_ok end,
1648    true = not_ok =:= FunM2(<<"1">>),
1649
1650    BL = [{3,4,5},{6,7,8}],
1651    Lst = [0,0,0,3,0,0,0,4,0,0,0,5,0,0,0,6,0,0,0,7,0,0,0,8],
1652    B1 = triples_to_bin1(BL),
1653    true = Lst =:= binary_to_list(B1),
1654    B2 = triples_to_bin2(BL),
1655    true = Lst =:= binary_to_list(B2),
1656
1657    [ok] = scan(
1658	     <<"Bin11 = <<1, 17, 42>>,
1659        true = [1, 17, 42] =:= binary_to_list(Bin11),
1660	       Bin12 = <<\"abc\">>,
1661        true = [97, 98, 99] =:= binary_to_list(Bin12),
1662
1663			 A = 1, B = 17, C = 42,
1664			 Bin2 = <<A, B, C:16>>,
1665			 true = [1, 17, 00, 42] =:= binary_to_list(Bin2),
1666			 <<D:16, E, F/binary>> = Bin2,
1667			 true = D =:= 273,
1668			 true = E =:= 00,
1669			 true = [42] =:= binary_to_list(F),
1670
1671			 Fun4 = fun(Dgram) ->
1672					DgramSize = byte_size(Dgram),
1673					case Dgram of
1674					    <<4:4, HLen:4, SrvcType:8, TotLen:16,
1675					      ID:16, Flgs:3, FragOff:13,
1676					      TTL:8, Proto:8, HdrChkSum:16,
1677					      SrcIP:32, DestIP:32,
1678					      RestDgram/binary>> when HLen>=5,
1679								      4*HLen=<DgramSize ->
1680						OptsLen = 4*(HLen - 5),
1681						<<Opts:OptsLen/binary,Data/binary>> = RestDgram,
1682						{SrvcType, TotLen, Flgs, FragOff, ID, HdrChkSum,
1683						 Proto, TTL, SrcIP, DestIP, Data, Opts};
1684					    _ ->
1685						not_ok
1686					end
1687				end,
1688			 true = Fun4(<<>>) =:= not_ok,
1689			 true = is_tuple(Fun4(list_to_binary
1690						([<<4:4,5:4>>,list_to_binary(lists:seq(1,255))]))),
1691
1692			 X = 23432324, Y = 24324234,
1693			 <<10:7>> = <<X:1, Y:6>>,
1694			 Z = 234324324,
1695			 XYZ = <<X:1, Y:6, Z:1>>,
1696			 true = [20] =:= binary_to_list(XYZ),
1697			 Hello1 = <<\"hello\">>,
1698        Hello2 = <<$h,$e,$l,$l,$o>>,
1699				    true = \"hello\" =:= binary_to_list(Hello1),
1700        true = \"hello\" =:= binary_to_list(Hello2),
1701
1702        FunM1 = fun(<<X1:7/binary, Y1:1/binary>>) -> {X1,Y1} end,
1703				    true = {<<\"1234567\">>,<<\"8\">>} =:= FunM1(<<\"12345678\">>),
1704
1705        FunM2 = fun(<<_X1:7/binary-unit:7, _Y1:1/binary-unit:1>>) -> ok;
1706                   (_) -> not_ok end,
1707					      true = not_ok =:= FunM2(<<\"1\">>),
1708        ok.">>),
1709
1710    ok.
1711
1712triples_to_bin1(T) ->
1713    triples_to_bin1(T, <<>>).
1714
1715triples_to_bin1([{X,Y,Z} | T], Acc) ->
1716    triples_to_bin1(T, <<Acc/binary, X:32, Y:32, Z:32>>);   % inefficient
1717triples_to_bin1([], Acc) ->
1718    Acc.
1719
1720triples_to_bin2(T) ->
1721    triples_to_bin2(T, []).
1722
1723triples_to_bin2([{X,Y,Z} | T], Acc) ->
1724    triples_to_bin2(T, [<<X:32, Y:32, Z:32>> | Acc]);
1725triples_to_bin2([], Acc) ->
1726    list_to_binary(lists:reverse(Acc)).
1727
1728%% Record examples from Programming Examples. OTP-5237.
1729progex_records(Config) when is_list(Config) ->
1730    Test1 =
1731	<<"-module(recs).
1732          -record(person, {name = \"\", phone = [], address}).
1733          -record(name, {first = \"Robert\", last = \"Ericsson\"}).
1734          -record(person2, {name = #name{}, phone}).
1735-export([t/0]).
1736
1737t() ->
1738    _P1 = #person{phone=[0,8,2,3,4,3,1,2], name=\"Robert\"},
1739              \"Robert\" = _P1#person.name,
1740              [0,8,2,3,4,3,1,2] = _P1#person.phone,
1741		  undefined = _P1#person.address,
1742
1743		  _P2 = #person{name = \"Jakob\", _ = '_'},
1744               \"Jakob\" = _P2#person.name,
1745              '_' = _P2#person.phone,
1746				'_' = _P2#person.address,
1747
1748				P = #person{name = \"Joe\", phone = [0,8,2,3,4,3,1,2]},
1749              \"Joe\" = P#person.name,
1750              [0,8,2,3,4,3,1,2] = P#person.phone,
1751					    undefined = P#person.address,
1752
1753					    P1 = #person{name=\"Joe\", phone=[1,2,3], address=\"A street\"},
1754              P2 = P1#person{name=\"Robert\"},
1755              \"Robert\" = P2#person.name,
1756              [1,2,3] = P2#person.phone,
1757			     \"A street\" = P2#person.address,
1758              a_person = foo(P1),
1759
1760			     {found, [1,2,3]} =
1761				 find_phone([#person{name = a},
1762					     #person{name = b, phone = [3,2,1]},
1763					     #person{name = c, phone = [1,2,3]}],
1764					    c),
1765
1766			     P3 = #person{name=\"Joe\", phone=[0,0,7], address=\"A street\"},
1767              #person{name = Name} = P3,
1768					  \"Joe\" = Name,
1769
1770              \"Robert\" = demo(),
1771              ok.
1772
1773foo(P) when is_record(P, person) -> a_person;
1774foo(_) -> not_a_person.
1775
1776find_phone([#person{name=Name, phone=Phone} | _], Name) ->
1777    {found,  Phone};
1778find_phone([_| T], Name) ->
1779    find_phone(T, Name);
1780find_phone([], _Name) ->
1781    not_found.
1782
1783demo() ->
1784    P = #person2{name= #name{first=\"Robert\",last=\"Virding\"},
1785                               phone=123},
1786		 _First = (P#person2.name)#name.first.
1787">>,
1788    ok = run_file(Config, recs, Test1),
1789
1790Test1_shell =
1791<<"rd(person, {name = \"\", phone = [], address}),
1792          rd(name, {first = \"Robert\", last = \"Ericsson\"}),
1793          rd(person2, {name = #name{}, phone}),
1794
1795		    _P1 = #person{phone=[0,8,2,3,4,3,1,2], name=\"Robert\"},
1796          \"Robert\" = _P1#person.name,
1797          [0,8,2,3,4,3,1,2] = _P1#person.phone,
1798				  undefined = _P1#person.address,
1799
1800				  _P2 = #person{name = \"Jakob\", _ = '_'},
1801           \"Jakob\" = _P2#person.name,
1802          '_' = _P2#person.phone,
1803						'_' = _P2#person.address,
1804
1805						P = #person{name = \"Joe\", phone = [0,8,2,3,4,3,1,2]},
1806          \"Joe\" = P#person.name,
1807          [0,8,2,3,4,3,1,2] = P#person.phone,
1808							    undefined = P#person.address,
1809
1810							    P1 = #person{name=\"Joe\", phone=[1,2,3], address=\"A street\"},
1811          P2 = P1#person{name=\"Robert\"},
1812          \"Robert\" = P2#person.name,
1813          [1,2,3] = P2#person.phone,
1814			 \"A street\" = P2#person.address,
1815          Foo = fun(P) when is_record(P, person) -> a_person;
1816                   (_) -> not_a_person
1817                end,
1818			 a_person = Foo(P1),
1819
1820			 Find = fun([#person{name=Name, phone=Phone} | _], Name, Fn) ->
1821					{found,  Phone};
1822				   ([_| T], Name, Fn) ->
1823					Fn(T, Name, Fn);
1824				   ([], _Name, _Fn) ->
1825					not_found
1826				end,
1827
1828			 {found, [1,2,3]} = Find([#person{name = a},
1829						  #person{name = b, phone = [3,2,1]},
1830						  #person{name = c, phone = [1,2,3]}],
1831						 c,
1832						 Find),
1833
1834			 P3 = #person{name=\"Joe\", phone=[0,0,7], address=\"A street\"},
1835          #person{name = Name} = P3,
1836				      \"Joe\" = Name,
1837
1838          Demo = fun() ->
1839			 P17 = #person2{name= #name{first=\"Robert\",last=\"Virding\"},
1840                           phone=123},
1841					_First = (P17#person2.name)#name.first
1842					end,
1843
1844					\"Robert\" = Demo(),
1845          ok.
1846">>,
1847    [ok] = scan(Test1_shell),
1848
1849Test2 =
1850<<"-module(recs).
1851          -record(person, {name, age, phone = [], dict = []}).
1852-export([t/0]).
1853
1854t() -> ok.
1855
1856make_hacker_without_phone(Name, Age) ->
1857    #person{name = Name, age = Age,
1858	    dict = [{computer_knowledge, excellent},
1859		    {drinks, coke}]}.
1860print(#person{name = Name, age = Age,
1861	      phone = Phone, dict = Dict}) ->
1862    io:format(\"Name: ~s, Age: ~w, Phone: ~w ~n\"
1863                        \"Dictionary: ~w.~n\", [Name, Age, Phone, Dict]).
1864
1865          birthday(P) when record(P, person) ->
1866		     P#person{age = P#person.age + 1}.
1867
1868register_two_hackers() ->
1869    Hacker1 = make_hacker_without_phone(\"Joe\", 29),
1870             OldHacker = birthday(Hacker1),
1871             %% The central_register_server should have
1872             %% an interface function for this.
1873					central_register_server ! {register_person, Hacker1},
1874					central_register_server ! {register_person,
1875								   OldHacker#person{name = \"Robert\",
1876                                        phone = [0,8,3,2,4,5,3,1]}}.
1877">>,
1878    ok = run_file(Config, recs, Test2),
1879ok.
1880
1881%% List comprehension examples from Programming Examples. OTP-5237.
1882progex_lc(Config) when is_list(Config) ->
1883    Test1 =
1884	<<"-module(lc).
1885          -export([t/0]).
1886
1887t() ->
1888    [a,4,b,5,6] = [X || X <- [1,2,a,3,4,b,5,6], X > 3],
1889    [4,5,6] = [X || X <- [1,2,a,3,4,b,5,6], integer(X), X > 3],
1890    [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
1891	[{X, Y} || X <- [1,2,3], Y <- [a,b]],
1892
1893    [1,2,3,4,5,6,7,8] = sort([4,5,1,8,3,6,7,2]),
1894    [[b,u,g],[b,g,u],[u,b,g],[u,g,b],[g,b,u],[g,u,b]] =
1895	perms([b,u,g]),
1896    [] = pyth(11),
1897    [{3,4,5},{4,3,5}] = pyth(12),
1898    [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
1899     {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
1900     {16,12,20}] = pyth(50),
1901    [] = pyth1(11),
1902    [{3,4,5},{4,3,5}] = pyth1(12),
1903    [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
1904     {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
1905     {16,12,20}] = pyth1(50),
1906    [1,2,3,4,5] = append([[1,2,3],[4,5]]),
1907    [2,3,4] = map(fun(X) -> X + 1 end, [1,2,3]),
1908    [2,4] = filter(fun(X) -> X > 1 end, [0,2,4]),
1909    [1,2,3,7] = select(b,[{a,1},{b,2},{c,3},{b,7}]),
1910    [2,7] = select2(b,[{a,1},{b,2},{c,3},{b,7}]),
1911    ok.
1912
1913sort([Pivot|T]) ->
1914    sort([ X || X <- T, X < Pivot]) ++
1915	[Pivot] ++
1916	sort([ X || X <- T, X >= Pivot]);
1917sort([]) -> [].
1918
1919perms([]) -> [[]];
1920perms(L)  -> [[H|T] || H <- L, T <- perms(L--[H])].
1921
1922pyth(N) ->
1923    [ {A,B,C} ||
1924	A <- lists:seq(1,N),
1925	B <- lists:seq(1,N),
1926	C <- lists:seq(1,N),
1927	A+B+C =< N,
1928	A*A+B*B == C*C
1929    ].
1930
1931pyth1(N) ->
1932    [{A,B,C} ||
1933	A <- lists:seq(1,N),
1934	B <- lists:seq(1,N-A+1),
1935	C <- lists:seq(1,N-A-B+2),
1936	A+B+C =< N,
1937	A*A+B*B == C*C ].
1938
1939append(L)   ->  [X || L1 <- L, X <- L1].
1940map(Fun, L) -> [Fun(X) || X <- L].
1941filter(Pred, L) -> [X || X <- L, Pred(X)].
1942
1943select(X, L) ->  [Y || {X, Y} <- L].
1944select2(X, L) ->  [Y || {X1, Y} <- L, X == X1].
1945">>,
1946    ok = run_file(Config, lc, Test1),
1947
1948Test1_shell =
1949<<"[a,4,b,5,6] = [X || X <- [1,2,a,3,4,b,5,6], X > 3],
1950          [4,5,6] = [X || X <- [1,2,a,3,4,b,5,6], integer(X), X > 3],
1951  [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
1952  [{X, Y} || X <- [1,2,3], Y <- [a,b]],
1953
1954  Sort = fun([Pivot|T], Fn) ->
1955		 Fn([ X || X <- T, X < Pivot], Fn) ++
1956		     [Pivot] ++
1957		     Fn([ X || X <- T, X >= Pivot], Fn);
1958	    ([], _Fn) -> []
1959	 end,
1960
1961  [1,2,3,4,5,6,7,8] = Sort([4,5,1,8,3,6,7,2], Sort),
1962  Perms = fun([], _Fn) -> [[]];
1963	     (L, Fn)  -> [[H|T] || H <- L, T <- Fn(L--[H], Fn)]
1964	  end,
1965  [[b,u,g],[b,g,u],[u,b,g],[u,g,b],[g,b,u],[g,u,b]] =
1966  Perms([b,u,g], Perms),
1967
1968  Pyth = fun(N) ->
1969		 [ {A,B,C} ||
1970		     A <- lists:seq(1,N),
1971		     B <- lists:seq(1,N),
1972		     C <- lists:seq(1,N),
1973		     A+B+C =< N,
1974		     A*A+B*B == C*C
1975		 ]
1976	 end,
1977
1978  [] = Pyth(11),
1979  [{3,4,5},{4,3,5}] = Pyth(12),
1980%%[{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
1981%% {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
1982%% {16,12,20}] = Pyth(50),
1983
1984  Pyth1 = fun(N) ->
1985		  [{A,B,C} ||
1986		      A <- lists:seq(1,N),
1987		      B <- lists:seq(1,N-A+1),
1988		      C <- lists:seq(1,N-A-B+2),
1989		      A+B+C =< N,
1990		      A*A+B*B == C*C ]
1991	  end,
1992
1993  [] = Pyth1(11),
1994  [{3,4,5},{4,3,5}] = Pyth1(12),
1995  [{3,4,5},{4,3,5},{5,12,13},{6,8,10},{8,6,10},{8,15,17},
1996   {9,12,15},{12,5,13},{12,9,15},{12,16,20},{15,8,17},
1997   {16,12,20}] = Pyth1(50),
1998
1999  Append = fun(L)   ->  [X || L1 <- L, X <- L1] end,
2000  [1,2,3,4,5] = Append([[1,2,3],[4,5]]),
2001  Map = fun(Fun, L) -> [Fun(X) || X <- L] end,
2002  [2,3,4] = Map(fun(X) -> X + 1 end, [1,2,3]),
2003  Filter = fun(Pred, L) -> [X || X <- L, Pred(X)] end,
2004  [2,4] = Filter(fun(X) -> X > 1 end, [0,2,4]),
2005
2006  Select = fun(X, L) ->  [Y || {X, Y} <- L] end,
2007  [1,2,3,7] = Select(b,[{a,1},{b,2},{c,3},{b,7}]),
2008  Select2 = fun(X, L) ->  [Y || {X1, Y} <- L, X == X1] end,
2009  [2,7] = Select2(b,[{a,1},{b,2},{c,3},{b,7}]),
2010  ok.
2011">>,
2012    [ok] = scan(Test1_shell),
2013ok.
2014
2015%% Funs examples from Programming Examples. OTP-5237.
2016progex_funs(Config) when is_list(Config) ->
2017    Test1 =
2018	<<"-module(funs).
2019          -export([t/0]).
2020
2021double([H|T]) -> [2*H|double(T)];
2022double([])    -> [].
2023
2024add_one([H|T]) -> [H+1|add_one(T)];
2025add_one([])    -> [].
2026
2027map(F, [H|T]) -> [F(H)|map(F, T)];
2028map(F, [])    -> [].
2029
2030double2(L)  -> map(fun(X) -> 2*X end, L).
2031add_one2(L) -> map(fun(X) -> 1 + X end, L).
2032
2033print_list(Stream, [H|T]) ->
2034    io:format(Stream, \"~p~n\", [H]),
2035              print_list(Stream, T);
2036		  print_list(Stream, []) ->
2037		     true.
2038
2039broadcast(Msg, [Pid|Pids]) ->
2040    Pid ! Msg,
2041    broadcast(Msg, Pids);
2042broadcast(_, []) ->
2043    true.
2044
2045foreach(F, [H|T]) ->
2046    F(H),
2047    foreach(F, T);
2048foreach(F, []) ->
2049    ok.
2050
2051print_list2(S, L) ->
2052    foreach(fun(H) -> io:format(S, \"~p~n\",[H]) end, L).
2053
2054          broadcast2(M, L) -> foreach(fun(Pid) -> Pid ! M end, L).
2055
2056t1() -> map(fun(X) -> 2 * X end, [1,2,3,4,5]).
2057
2058t2() -> map(fun double/1, [1,2,3,4,5]).
2059
2060t3() -> map({?MODULE, double3}, [1,2,3,4,5]).
2061
2062double3(X) -> X * 2.
2063
2064f(F, Args) when function(F) ->
2065    apply(F, Args);
2066f(N, _) when integer(N) ->
2067    N.
2068
2069print_list3(File, List) ->
2070    {ok, Stream} = file:open(File, write),
2071    foreach(fun(X) -> io:format(Stream,\"~p~n\",[X]) end, List),
2072              file:close(Stream).
2073
2074print_list4(File, List) ->
2075    {ok, Stream} = file:open(File, write),
2076    foreach(fun(File) ->
2077		    io:format(Stream,\"~p~n\",[File])
2078                      end, List),
2079		    file:close(Stream).
2080
2081any(Pred, [H|T]) ->
2082    case Pred(H) of
2083	true  ->  true;
2084	false ->  any(Pred, T)
2085    end;
2086any(Pred, []) ->
2087    false.
2088
2089all(Pred, [H|T]) ->
2090    case Pred(H) of
2091	true  ->  all(Pred, T);
2092	false ->  false
2093    end;
2094all(Pred, []) ->
2095    true.
2096
2097foldl(F, Accu, [Hd|Tail]) ->
2098    foldl(F, F(Hd, Accu), Tail);
2099foldl(F, Accu, []) -> Accu.
2100
2101mapfoldl(F, Accu0, [Hd|Tail]) ->
2102    {R,Accu1} = F(Hd, Accu0),
2103    {Rs,Accu2} = mapfoldl(F, Accu1, Tail),
2104    {[R|Rs], Accu2};
2105mapfoldl(F, Accu, []) -> {[], Accu}.
2106
2107filter(F, [H|T]) ->
2108    case F(H) of
2109	true  -> [H|filter(F, T)];
2110	false -> filter(F, T)
2111    end;
2112filter(F, []) -> [].
2113
2114diff(L1, L2) ->
2115    filter(fun(X) -> not lists:member(X, L2) end, L1).
2116
2117intersection(L1,L2) -> filter(fun(X) -> lists:member(X,L1) end, L2).
2118
2119takewhile(Pred, [H|T]) ->
2120    case Pred(H) of
2121	true  -> [H|takewhile(Pred, T)];
2122	false -> []
2123    end;
2124takewhile(Pred, []) ->
2125    [].
2126
2127dropwhile(Pred, [H|T]) ->
2128    case Pred(H) of
2129	true  -> dropwhile(Pred, T);
2130	false -> [H|T]
2131    end;
2132dropwhile(Pred, []) ->
2133    [].
2134
2135splitlist(Pred, L) ->
2136    splitlist(Pred, L, []).
2137
2138splitlist(Pred, [H|T], L) ->
2139    case Pred(H) of
2140	true  -> splitlist(Pred, T, [H|L]);
2141	false -> {lists:reverse(L), [H|T]}
2142    end;
2143splitlist(Pred, [], L) ->
2144    {lists:reverse(L), []}.
2145
2146first(Pred, [H|T]) ->
2147    case Pred(H) of
2148	true ->
2149	    {true, H};
2150	false ->
2151	    first(Pred, T)
2152    end;
2153first(Pred, []) ->
2154    false.
2155
2156ints_from(N) ->
2157    fun() ->
2158	    [N|ints_from(N+1)]
2159    end.
2160
2161pconst(X) ->
2162    fun (T) ->
2163	    case T of
2164		[X|T1] -> {ok, {const, X}, T1};
2165		_      -> fail
2166	    end
2167    end.
2168
2169pand(P1, P2) ->
2170    fun (T) ->
2171	    case P1(T) of
2172		{ok, R1, T1} ->
2173		    case P2(T1) of
2174			{ok, R2, T2} ->
2175			    {ok, {'and', R1, R2}};
2176			fail ->
2177			    fail
2178		    end;
2179		fail ->
2180		    fail
2181	    end
2182    end.
2183
2184por(P1, P2) ->
2185    fun (T) ->
2186	    case P1(T) of
2187		{ok, R, T1} ->
2188		    {ok, {'or',1,R}, T1};
2189		fail ->
2190		    case P2(T) of
2191			{ok, R1, T1} ->
2192			    {ok, {'or',2,R1}, T1};
2193			fail ->
2194			    fail
2195		    end
2196	    end
2197    end.
2198
2199grammar() ->
2200    pand(
2201      por(pconst(a), pconst(b)),
2202      por(pconst(c), pconst(d))).
2203
2204parse(List) ->
2205    (grammar())(List).
2206
2207
2208t() ->
2209    [2,4,6,8] = double([1,2,3,4]),
2210    [2,3,4,5] = add_one([1,2,3,4]),
2211    [2,4,6,8] = double2([1,2,3,4]),
2212    [2,3,4,5] = add_one2([1,2,3,4]),
2213    XX = ints_from(1),
2214    [1 | _] = XX(),
2215    1 = hd(XX()),
2216    Y = tl(XX()),
2217    2 = hd(Y()),
2218
2219    P1 = pconst(a),
2220    {ok,{const,a},[b,c]} = P1([a,b,c]),
2221    fail = P1([x,y,z]),
2222
2223    {ok,{'and',{'or',1,{const,a}},{'or',1,{const,c}}}} =
2224	parse([a,c]),
2225    {ok,{'and',{'or',1,{const,a}},{'or',2,{const,d}}}} =
2226	parse([a,d]),
2227    {ok,{'and',{'or',2,{const,b}},{'or',1,{const,c}}}} =
2228	parse([b,c]),
2229    {ok,{'and',{'or',2,{const,b}},{'or',2,{const,d}}}} =
2230	parse([b,d]),
2231    fail = parse([a,b]),
2232    ok.
2233">>,
2234    ok = run_file(Config, funs, Test1),
2235
2236Test2_shell =
2237<<"Double = fun(X) -> 2 * X end,
2238          [2,4,6,8,10] = lists:map(Double, [1,2,3,4,5]),
2239
2240  Big =  fun(X) -> if X > 10 -> true; true -> false end end,
2241  false = lists:any(Big, [1,2,3,4]),
2242  true = lists:any(Big, [1,2,3,12,5]),
2243  false = lists:all(Big, [1,2,3,4,12,6]),
2244  true = lists:all(Big, [12,13,14,15]),
2245  L = [\"I\",\"like\",\"Erlang\"],
2246          11 = lists:foldl(fun(X, Sum) -> length(X) + Sum end, 0, L),
2247       Upcase =  fun(X) when $a =< X,  X =< $z -> X + $A - $a;
2248		    (X) -> X
2249		 end,
2250       Upcase_word = fun(X) -> lists:map(Upcase, X) end,
2251       \"ERLANG\" = Upcase_word(\"Erlang\"),
2252          [\"I\",\"LIKE\",\"ERLANG\"] = lists:map(Upcase_word, L),
2253          {[\"I\",\"LIKE\",\"ERLANG\"],11} =
2254               lists:mapfoldl(fun(Word, Sum) ->
2255				      {Upcase_word(Word), Sum + length(Word)}
2256                              end, 0, L),
2257	    [500,12,45] = lists:filter(Big, [500,12,2,45,6,7]),
2258	    [200,500,45] = lists:takewhile(Big, [200,500,45,5,3,45,6]),
2259	    [5,3,45,6] = lists:dropwhile(Big, [200,500,45,5,3,45,6]),
2260	    {[200,500,45],[5,3,45,6]} =
2261		lists:splitwith(Big, [200,500,45,5,3,45,6]),
2262          %% {true,45} = lists:first(Big, [1,2,45,6,123]),
2263          %% false = lists:first(Big, [1,2,4,5]),
2264
2265	    Adder = fun(X) -> fun(Y) -> X + Y end end,
2266	    Add6 = Adder(6),
2267	    16 = Add6(10),
2268	    ok.
2269">>,
2270    [ok] = scan(Test2_shell),
2271ok.
2272
2273
2274%% OTP-5990. {erlang,is_record}.
2275otp_5990(Config) when is_list(Config) ->
2276    [true] =
2277        scan(<<"rd('OrdSet', {orddata = {},ordtype = type}), "
2278               "S = #'OrdSet'{ordtype = {}}, "
2279               "if tuple(S#'OrdSet'.ordtype) -> true; true -> false end.">>),
2280    ok.
2281
2282%% OTP-6166. Order of record definitions.
2283otp_6166(Config) when is_list(Config) ->
2284    Test1 = filename:join(proplists:get_value(priv_dir, Config), "test1.hrl"),
2285    Contents1 = <<"-module(test1).
2286                   -record(r5, {f}). -record(r3, {f = #r5{}}). "
2287                  "-record(r1, {f = #r3{}}). -record(r4, {f = #r1{}}). "
2288"-record(r2, {f = #r4{}}).">>,
2289    ok = file:write_file(Test1, Contents1),
2290
2291    Test2 = filename:join(proplists:get_value(priv_dir, Config), "test2.hrl"),
2292    Contents2 = <<"-module(test2).
2293                   -record(r5, {f}). -record(r3, {f = #r5{}}). "
2294                  "-record(r1, {f = #r3{}}). -record(r4, {f = #r1{}}). "
2295                  "-record(r2, {f = #r4{}}).
2296                   -record(r6, {f = #r5{}}).            % r6 > r0
2297                   -record(r0, {f = #r5{}, g = #r5{}}). % r0 < r5">>,
2298    ok = file:write_file(Test2, Contents2),
2299
2300    RR12 = "[r1,r2,r3,r4,r5] = rr(\"" ++ Test1 ++ "\"),
2301            [r0,r1,r2,r3,r4,r5,r6] = rr(\"" ++ Test2 ++ "\"),
2302            R0 = #r0{}, R6 = #r6{},
2303            true = is_record(R0, r0),
2304            true = is_record(R6, r6),
2305            ok. ",
2306    [ok] = scan(RR12),
2307
2308    file:delete(Test1),
2309    file:delete(Test2),
2310    ok.
2311
2312%% OTP-6554. Formatted exits and error messages.
2313otp_6554(Config) when is_list(Config) ->
2314    %% Should check the stacktrace as well...
2315    "exception error: bad argument" =
2316        comm_err(<<"math:sqrt(a).">>),
2317    "exception error: bad argument" =
2318        comm_err(<<"fun(X, Y) -> X ++ Y end(a, b).">>),
2319    "exception error: bad argument" =
2320        comm_err(<<"math:sqrt(lists:seq(1,40)).">>),
2321    "exception error: bad argument" =
2322        comm_err(<<"math:sqrt(lists:seq(1,10)).">>),
2323    "exception error: bad argument" =
2324        comm_err(<<"a ++ b.">>),
2325    "exception error: bad argument" =
2326        comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
2327                         undefined,undefined,undefined,undefined,undefined,
2328                         undefined,undefined,undefined,undefined},
2329                    aa ++ I.">>),
2330    "exception error: bad argument" =
2331        comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
2332                         undefined,undefined,undefined,undefined,undefined,
2333                         undefined,undefined,undefined,undefined},
2334                    aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa ++ I.">>),
2335    "exception error: bad argument" =
2336        comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
2337                         undefined,undefined,undefined,undefined,undefined,
2338                         undefined,undefined,undefined,undefined},
2339                    I ++ I.">>),
2340    "exception error: bad argument" =
2341        comm_err(<<"fun(X) -> not X end(a).">>),
2342    "exception error: bad argument: a" =
2343        comm_err(<<"fun(A, B) -> A orelse B end(a, b).">>),
2344    "exception error: an error occurred when evaluating an arithmetic expression" =
2345        comm_err(<<"math:sqrt(2)/round(math:sqrt(0)).">>),
2346    "exception error: interpreted function with arity 1 called with no arguments" =
2347        comm_err(<<"fun(V) -> V end().">>),
2348    "exception error: interpreted function with arity 1 called with two arguments" =
2349        comm_err(<<"fun(V) -> V end(1,2).">>),
2350    "exception error: interpreted function with arity 0 called with one argument" =
2351        comm_err(<<"fun() -> v end(1).">>),
2352    "exception error: interpreted function with arity 0 called with 4 arguments" =
2353        comm_err(<<"fun() -> v end(1,2,3,4).">>),
2354    "exception error: math:sqrt/1 called with two arguments" =
2355        comm_err(<<"fun math:sqrt/1(1,2).">>),
2356    "exception error: bad function 1." ++ _ =
2357        comm_err(<<"(math:sqrt(2))().">>),
2358    "exception error: bad function [1," ++ _ =
2359        comm_err(<<"(lists:seq(1, 100))().">>),
2360    "exception error: no match of right hand side value 1" ++ _ =
2361        comm_err(<<"a = math:sqrt(2).">>),
2362    "exception error: no match of right hand side value" ++ _ =
2363        comm_err(<<"I = {file_info,undefined,undefined,undefined,undefined,
2364                         undefined,undefined,undefined,undefined,undefined,
2365                         undefined,undefined,undefined,undefined},
2366                    a = I.">>),
2367    "exception error: no case clause matching 1" ++ _ =
2368        comm_err(<<"case math:sqrt(2) of a -> ok end.">>),
2369    "exception error: no case clause matching [1," ++ _ =
2370        comm_err(<<"V = lists:seq(1, 20), case V of a -> ok end.">>),
2371    "exception error: no function clause matching" =
2372        comm_err(<<"fun(P) when is_pid(P) -> true end(a).">>),
2373    case test_server:is_native(erl_eval) of
2374	true ->
2375	    %% Native code has different exit reason. Don't bother
2376	    %% testing them.
2377	    ok;
2378	false ->
2379	    "exception error: {function_clause," =
2380		comm_err(<<"erlang:error(function_clause, "
2381			  "[unproper | list]).">>),
2382	    %% Cheating:
2383	    "exception error: no function clause matching "
2384		"shell:apply_fun(4)" ++ _ =
2385		comm_err(<<"erlang:error(function_clause, [4]).">>),
2386		"exception error: no function clause matching "
2387		"lists:reverse(" ++ _ =
2388		comm_err(<<"F=fun() -> hello end, lists:reverse(F).">>),
2389		"exception error: no function clause matching "
2390		"lists:reverse(34) (lists.erl, line " ++ _ =
2391		comm_err(<<"lists:reverse(34).">>)
2392    end,
2393    "exception error: function_clause" =
2394        comm_err(<<"erlang:error(function_clause, 4).">>),
2395    "exception error: no function clause matching" ++ _ =
2396        comm_err(<<"fun(a, b, c, d) -> foo end"
2397                   "       (lists:seq(1,17),"
2398                   "        lists:seq(1, 18),"
2399                   "        lists:seq(1, 40),"
2400                   "        lists:seq(1, 5)).">>),
2401
2402    "exception error: no function clause matching" =
2403        comm_err(<<"fun(P, q) when is_pid(P) -> true end(a, b).">>),
2404    "exception error: no true branch found when evaluating an if expression" =
2405        comm_err(<<"if length([a,b]) > 17 -> a end.">>),
2406    "exception error: no such process or port" =
2407        comm_err(<<"Pid = spawn(fun() -> a end),"
2408                   "timer:sleep(1),"
2409                   "link(Pid).">>),
2410    "exception error: a system limit has been reached" =
2411        comm_err(<<"list_to_atom(lists:duplicate(300,$a)).">>),
2412    "exception error: bad receive timeout value" =
2413        comm_err(<<"receive after a -> foo end.">>),
2414    "exception error: no try clause matching 1" ++ _ =
2415        comm_err(<<"try math:sqrt(2) of bar -> yes after 3 end.">>),
2416    "exception error: no try clause matching [1" ++ _ =
2417        comm_err(<<"V = lists:seq(1, 20),"
2418                   "try V of bar -> yes after 3 end.">>),
2419    "exception error: undefined function math:sqrt/2" =
2420        comm_err(<<"math:sqrt(2, 2).">>),
2421    "exception error: limit of number of arguments to interpreted function "
2422          "exceeded" =
2423        comm_err(<<"fun(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U) ->"
2424                   "   a end().">>),
2425    "exception error: bad filter a" =
2426        comm_err(<<"[b || begin a end].">>),
2427    "exception error: bad generator a" =
2428        comm_err(<<"[X || X <- a].">>),
2429    "exception throw: undef" = comm_err(<<"throw(undef).">>),
2430    "exception exit: undef" = comm_err(<<"exit(undef).">>),
2431
2432    "exception exit: foo" =
2433          comm_err(<<"catch spawn_link(fun() ->"
2434                     "                     timer:sleep(300), exit(foo) "
2435                     "                 end),"
2436                     "timer:sleep(500).">>),
2437    [ok] = scan(
2438                   <<"begin process_flag(trap_exit, true),"
2439                     "  Pid = spawn_link(fun() ->"
2440                     "                       timer:sleep(300), exit(foo) "
2441                     "                   end),"
2442                     "  timer:sleep(500),"
2443                     "  receive {'EXIT', Pid, foo} -> ok end end.">>),
2444    "exception exit: badarith" =
2445          comm_err(<<"catch spawn_link(fun() ->"
2446                     "                     timer:sleep(300), 1/0 "
2447                     "                 end),"
2448                     "timer:sleep(500).">>),
2449    "exception exit: {nocatch,foo}" =
2450          comm_err(<<"catch spawn_link(fun() ->"
2451                     "                     timer:sleep(300), throw(foo) "
2452                     "                 end),"
2453                     "timer:sleep(500).">>),
2454    [ok] = scan(
2455                   <<"begin process_flag(trap_exit, true),"
2456                     "  Pid = spawn_link(fun() ->"
2457                     "                       timer:sleep(300), throw(foo) "
2458                     "                   end),"
2459                     "  timer:sleep(500),"
2460                     "  receive {'EXIT', Pid, {{nocatch,foo},_}} -> ok end "
2461                     "end.">>),
2462
2463    "exception error: an error occurred when evaluating an arithmetic expression" =
2464        comm_err(<<"begin catch_exception(true), 1/0 end.">>),
2465    "exception error: an error occurred when evaluating an arithmetic expression" =
2466        comm_err(<<"begin catch_exception(false), 1/0 end.">>),
2467    "exception error: no function clause matching call to catch_exception/1" =
2468        comm_err(<<"catch_exception(1).">>),
2469
2470    %% A bug was corrected (expansion of 'try'):
2471    "2: command not found" =
2472        comm_err(<<"try 1 of 1 -> v(2) after 3 end.">>),
2473    %% Cover a few lines:
2474    "3: command not found" =
2475        comm_err(<<"receive foo -> foo after 0 -> v(3) end.">>),
2476    "3: command not found" =
2477        comm_err(<<"receive foo -> foo after 0 -> e(3) end.">>),
2478    "1 / 0: command not found" = comm_err(<<"v(1/0).">>),
2479    "1\n1.\n" = t(<<"1. e(1).">>),
2480    [ok] = scan(<<"h().">>),
2481    "exception exit: normal" = comm_err(<<"exit(normal).">>),
2482    [foo] = scan(<<"begin history(0), foo end.">>),
2483    application:unset_env(stdlib, shell_history_length),
2484    [true] = scan(<<"begin <<10:(1024*1024*10)>>,"
2485                          "<<10:(1024*1024*10)>>, garbage_collect() end.">>),
2486    "1: syntax error before: '.'" = comm_err("1-."),
2487    %% comm_err(<<"exit().">>), % would hang
2488    "exception error: no function clause matching call to history/1" =
2489        comm_err(<<"history(foo).">>),
2490    "exception error: no function clause matching call to results/1" =
2491        comm_err(<<"results(foo).">>),
2492
2493    Test = filename:join(proplists:get_value(priv_dir, Config),
2494			       "otp_6554.erl"),
2495    Contents = <<"-module(otp_6554).
2496                  -export([local_allowed/3, non_local_allowed/3]).
2497                  local_allowed(_,_,State) ->
2498                      {true,State}.
2499
2500                  non_local_allowed(_,_,State) ->
2501                      {true,State}.
2502                 ">>,
2503    ok = compile_file(Config, Test, Contents, []),
2504    "exception exit: restricted shell starts now" =
2505	comm_err(<<"begin shell:start_restricted(otp_6554) end.">>),
2506    "-record(r,{}).\n1.\nok.\n" =
2507                    t(<<"f(), f(B), h(), b(), history(20), results(20),"
2508                        "rd(r, {}), rl(r), rf('_'), rl(), rf(),"
2509                        "rp(1), _ = rr({foo}), _ = rr({foo}, []),"
2510                        "rr({foo}, [], []), ok.">>),
2511    "false.\n" = t(<<"catch_exception(true).">>),
2512    "exception exit: restricted shell stopped"=
2513	comm_err(<<"begin shell:stop_restricted() end.">>),
2514    "true.\n" = t(<<"catch_exception(false).">>),
2515
2516    "20\n1\n1\n1: results(2)\n2: 1\n-> 1\n3: v(2)\n-> 1.\nok.\n" =
2517             t(<<"results(2). 1. v(2). h().">>),
2518    application:unset_env(stdlib, shell_saved_results),
2519    "1\nfoo\n17\nB = foo\nC = 17\nF = fun() ->\n           foo"
2520          "\n    end.\nok.\n" =
2521        t(<<"begin F = fun() -> foo end, 1 end. B = F(). C = 17. b().">>),
2522
2523    "3: command not found" = comm_err(<<"#{v(3) => v}.">>),
2524    "3: command not found" = comm_err(<<"#{k => v(3)}.">>),
2525    "3: command not found" = comm_err(<<"#{v(3) := v}.">>),
2526    "3: command not found" = comm_err(<<"#{k := v(3)}.">>),
2527    "3: command not found" = comm_err(<<"(v(3))#{}.">>),
2528    %% Tests I'd like to do: (you should try them manually)
2529    %% "catch spawn_link(fun() -> timer:sleep(1000), exit(foo) end)."
2530    %%   "** exception error: foo" should be output after 1 second
2531    %% "catch spawn_link(fun() -> timer:sleep(1000), 1/0 end)."
2532    %%   "** exception error: bad argument..." should be output after 1 second
2533    %% "1/0", "exit(foo)", "throw(foo)".
2534    %%   "h()." should show {'EXIT', {badarith,..}}, {'EXIT',{foo,...}},
2535    %%   and {'EXIT',{{nocatch,foo},...}}.
2536
2537    ok.
2538
2539%% OTP-7184. Propagate exit signals from dying evaluator process.
2540otp_7184(Config) when is_list(Config) ->
2541    register(otp_7184, self()),
2542    catch
2543           t(<<"P = self(),
2544                spawn_link(fun() -> process_flag(trap_exit,true),
2545                                    P ! up,
2546                                    receive X ->
2547                                        otp_7184 ! {otp_7184, X}
2548                                    end
2549                           end),
2550                receive up -> ok end,
2551                erlang:raise(throw, thrown, []).">>),
2552    receive {otp_7184,{'EXIT',_,{{nocatch,thrown},[]}}} -> ok end,
2553
2554    catch
2555           t(<<"P = self(),
2556                spawn_link(fun() -> process_flag(trap_exit,true),
2557                                    P ! up,
2558                                    receive X ->
2559                                        otp_7184 ! {otp_7184, X}
2560                                    end
2561                           end),
2562                receive up -> ok end,
2563                erlang:raise(exit, fini, []).">>),
2564    receive {otp_7184,{'EXIT',_,{fini,[]}}} -> ok end,
2565
2566    catch
2567           t(<<"P = self(),
2568                spawn_link(fun() -> process_flag(trap_exit,true),
2569                                    P ! up,
2570                                    receive X ->
2571                                        otp_7184 ! {otp_7184,X}
2572                                    end
2573                           end),
2574                receive up -> ok end,
2575                erlang:raise(error, bad, []).">>),
2576    receive {otp_7184,{'EXIT',_,{bad,[]}}} -> ok end,
2577
2578    unregister(otp_7184),
2579
2580    %% v/1, a few missed cases
2581    "17\n<<0,0,0,64>>.\nok.\n" =
2582        t(<<"17. "
2583            "<<64:32>>. "
2584           "<<64>> = << << X >> || << X >>  <= v(2), X > v(1) >>, ok.">>),
2585
2586    "17\n<<0,17>>.\n" =t(<<"17. <<(v(1)):16>>.">>),
2587
2588    ok.
2589
2590%% OTP-7232. qlc:info() bug.
2591otp_7232(Config) when is_list(Config) ->
2592    Info = <<"qlc:info(qlc:sort(qlc:q([X || X <- [55296,56296]]), "
2593             "{order, fun(A,B)-> A>B end})).">>,
2594    "qlc:sort([55296, 56296],\n"
2595    "         [{order,\n"
2596    "           fun(A, B) ->\n"
2597    "                  A > B\n"
2598    "           end}])" = evaluate(Info, []),
2599    ok.
2600
2601%% OTP-8393. Prompt string.
2602otp_8393(Config) when is_list(Config) ->
2603    _ = shell:prompt_func(default),
2604    "Bad prompt function: '> '" =
2605        prompt_err(<<"shell:prompt_func('> ').">>),
2606
2607    _ = shell:prompt_func(default),
2608    "exception error: an error occurred when evaluating an arithmetic expression"++_ =
2609        prompt_err(<<"shell:prompt_func({shell_SUITE,prompt4}).">>),
2610
2611    _ = shell:prompt_func(default),
2612    "default.\n" =
2613        t(<<"shell:prompt_func({shell_SUITE,prompt2}).">>),
2614
2615    _ = shell:prompt_func(default),
2616    "default\nl.\n" =
2617        t(<<"shell:prompt_func({shell_SUITE,prompt3}). l.">>),
2618
2619    %%
2620    %% Although this tests that you can set a unicode prompt function
2621    %% it does not really test that it does work with the io-servers.
2622    %% That is instead tested in the io_proto_SUITE, which has
2623    %% the right infrastructure in place for such tests. /PaN
2624    %%
2625    _ = shell:prompt_func(default),
2626    "default\nl.\n" =
2627        t(<<"shell:prompt_func({shell_SUITE,prompt5}). l.">>),
2628
2629    %% Restricted shell.
2630    Contents = <<"-module(test_restricted_shell).
2631                  -export([local_allowed/3, non_local_allowed/3]).
2632                  local_allowed(_,_,State) ->
2633                      {false,State}.
2634
2635                  non_local_allowed({shell,stop_restricted},[],State) ->
2636                      {true,State};
2637                  non_local_allowed({shell,prompt_func},[_L],State) ->
2638                      {true,State};
2639                  non_local_allowed({shell_SUITE,prompt1},[_L],State) ->
2640                      {true,State};
2641                  non_local_allowed(_,_,State) ->
2642                      {false,State}.
2643                 ">>,
2644    Test = filename:join(proplists:get_value(priv_dir, Config),
2645			       "test_restricted_shell.erl"),
2646    ok = compile_file(Config, Test, Contents, []),
2647    _ = shell:prompt_func(default),
2648    "exception exit: restricted shell starts now" =
2649	comm_err(<<"begin shell:start_restricted("
2650			 "test_restricted_shell) end.">>),
2651    "default.\n"++_ =
2652        t(<<"shell:prompt_func({shell_SUITE,prompt1}).">>),
2653    "exception exit: restricted shell does not allow apple(" ++ _ =
2654	comm_err(<<"apple(1).">>),
2655    "{shell_SUITE,prompt1}.\n" =
2656        t(<<"shell:prompt_func(default).">>),
2657    "exception exit: restricted shell stopped"=
2658	comm_err(<<"begin shell:stop_restricted() end.">>),
2659    undefined =
2660	application:get_env(stdlib, restricted_shell),
2661
2662    NR = shell:results(20),
2663    "default\n20.\n" =
2664        t(<<"shell:prompt_func({shell_SUITE,prompt3}). results(0).">>),
2665
2666    _ = shell:prompt_func(default),
2667    0 = shell:results(NR),
2668    ok.
2669
2670prompt1(_L) ->
2671    "prompt> ".
2672
2673prompt2(_L) ->
2674    {'EXIT', []}.
2675
2676prompt3(L) ->
2677    N = proplists:get_value(history, L),
2678    integer_to_list(N).
2679
2680prompt4(_L) ->
2681    erlang:apply(fun erlang:'/'/2, [1,0]).
2682
2683prompt5(_L) ->
2684    [1050,1072,1082,1074,1086,32,1077,32,85,110,105,99,111,100,101,32,63].
2685
2686-ifdef(not_used).
2687exit_term(B) ->
2688    "** exception exit:" ++ Reply = t(B),
2689    S0 = string:left(Reply, string:chr(Reply, $\n)-1),
2690    S = string:strip(S0, right, $*),
2691    {ok,Ts,_} = erl_scan:string(S),
2692    {ok,Term} = erl_parse:parse_term(Ts),
2693    Term.
2694-endif.
2695
2696error_string(B) ->
2697    "** exception error:" ++ Reply = t(B),
2698    caught_string(Reply).
2699
2700exit_string(B) ->
2701    "** exception exit:" ++ Reply = t(B),
2702    caught_string(Reply).
2703
2704caught_string(Reply) ->
2705    S0 = string:left(Reply, string:chr(Reply, $\n)-1),
2706    S1 = string:strip(S0, right, $.),
2707    S2 = string:strip(S1, left, $*),
2708    S =  string:strip(S2, both, $ ),
2709    string:strip(S, both, $").
2710
2711comm_err(B) ->
2712    Reply = t(B),
2713    S0 = string:left(Reply, string:chr(Reply, $\n)-1),
2714    S1 = string:strip(S0, left, $*),
2715    S2 = string:strip(S1, both, $ ),
2716    S = string:strip(S2, both, $"),
2717    string:strip(S, right, $.).
2718
2719prompt_err(B) ->
2720    Reply = t(B),
2721    S00 = string:sub_string(Reply, string:chr(Reply, $\n)+1),
2722    S0 = string:left(S00, string:chr(S00, $\n)-1),
2723    S1 = string:strip(S0, left, $*),
2724    S2 = string:strip(S1, both, $ ),
2725    S = string:strip(S2, both, $"),
2726    string:strip(S, right, $.).
2727
2728%% OTP-10302. Unicode. Also OTP-14285, Unicode atoms.
2729otp_10302(Config) when is_list(Config) ->
2730    {ok,Node} = start_node(shell_suite_helper_2,
2731			   "-pa "++proplists:get_value(priv_dir,Config)++
2732			   " +pc unicode"),
2733    Test1 =
2734        <<"begin
2735               io:setopts([{encoding,utf8}]),
2736               [1024] = \"\\x{400}\",
2737               rd(rec, {a = \"\\x{400}\"}),
2738               ok = rl(rec)
2739            end.">>,
2740    "-record(rec,{a = \"\x{400}\"}).\nok.\n" = t({Node,Test1}),
2741
2742    Test3 =
2743        <<"io:setopts([{encoding,utf8}]).
2744           rd(rec, {a = \"\\x{400}\"}).
2745           ok = rp(#rec{}).">>,
2746    "ok.\nrec\n#rec{a = \"\x{400}\"}.\nok.\n" = t({Node,Test3}),
2747
2748    Test4 =
2749        <<"io:setopts([{encoding,utf8}]).
2750           A = [1024] = \"\\x{400}\".
2751           b().
2752           h().">>,
2753
2754    "ok.\n\"\x{400}\"\nA = \"\x{400}\".\nok.\n"
2755    "1: io:setopts([{encoding, utf8}])\n-> ok.\n"
2756    "2: A = [1024] = \"\x{400}\"\n-> \"\x{400}\"\n"
2757    "3: b()\n-> ok.\nok.\n" = t({Node,Test4}),
2758
2759    Test5 =
2760        <<"begin
2761               io:setopts([{encoding,utf8}]),
2762               results(0),
2763               A = [1024] = \"\\x{400}\",
2764               b(),
2765               h()
2766           end.">>,
2767    "A = \"\x{400}\".\nok.\n" = t({Node,Test5}),
2768
2769    %% One $" is "lost":
2770    true =
2771       "\x{400}\": command not found" =:=
2772       prompt_err({Node,
2773                   <<"io:setopts([{encoding,utf8}]). v(\"\x{400}\")."/utf8>>,
2774                   unicode}),
2775
2776    "ok.\ndefault\n* Bad prompt function: \"\x{400}\".\n" =
2777        t({Node,<<"io:setopts([{encoding,utf8}]). "
2778             "shell:prompt_func(\"\x{400}\")."/utf8>>,
2779           unicode}),
2780    rpc:call(Node,shell, prompt_func, [default]),
2781    _ = shell:prompt_func(default),
2782
2783    %% Test erl_error:format_exception() (cf. OTP-6554)
2784    Test6 =
2785        <<"begin
2786               A = <<\"\\xaa\">>,
2787               S = lists:flatten(io_lib:format(\"~p/~p.\", [A, A])),
2788               {ok, Ts, _} = erl_scan:string(S, 1),
2789               {ok, Es} = erl_parse:parse_exprs(Ts),
2790               B = erl_eval:new_bindings(),
2791               erl_eval:exprs(Es, B)
2792           end.">>,
2793
2794    "** exception error: an error occurred when evaluating"
2795        " an arithmetic expression\n     in operator  '/'/2\n"
2796        "        called as <<\"\xaa\">> / <<\"\xaa\">>.\n" = t(Test6),
2797    Test7 =
2798        <<"io:setopts([{encoding,utf8}]).
2799           A = <<\"\\xaa\">>,
2800           S = lists:flatten(io_lib:format(\"~p/~p.\", [A, A])),
2801           {ok, Ts, _} = erl_scan:string(S, 1),
2802           {ok, Es} = erl_parse:parse_exprs(Ts),
2803           B = erl_eval:new_bindings(),
2804           erl_eval:exprs(Es, B).">>,
2805
2806    "ok.\n** exception error: an error occurred when evaluating"
2807        " an arithmetic expression\n     in operator  '/'/2\n"
2808        "        called as <<\"ª\">> / <<\"ª\">>.\n" = t({Node,Test7}),
2809    Test8 =
2810        <<"begin
2811               A = [1089],
2812               S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
2813               {ok, Ts, _} = erl_scan:string(S, 1),
2814               {ok, Es} = erl_parse:parse_exprs(Ts),
2815               B = erl_eval:new_bindings(),
2816               erl_eval:exprs(Es, B)
2817           end.">>,
2818    "** exception error: an error occurred when evaluating"
2819        " an arithmetic expression\n     in operator  '/'/2\n"
2820        "        called as [1089] / [1089].\n" = t(Test8),
2821    Test9 =
2822        <<"io:setopts([{encoding,utf8}]).
2823           A = [1089],
2824           S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
2825           {ok, Ts, _} = erl_scan:string(S, 1),
2826           {ok, Es} = erl_parse:parse_exprs(Ts),
2827           B = erl_eval:new_bindings(),
2828           erl_eval:exprs(Es, B).">>,
2829
2830    "ok.\n** exception error: an error occurred when evaluating"
2831        " an arithmetic expression\n     in operator  '/'/2\n"
2832        "        called as \"\x{441}\" / \"\x{441}\".\n" = t({Node,Test9}),
2833    Test10 =
2834        <<"A = {\"1\\xaa\",
2835           $\\xaa,
2836           << <<\"hi\">>/binary >>,
2837           <<\"1\xaa\">>},
2838           fun(a) -> true end(A).">>,
2839    "** exception error: no function clause matching \n"
2840    "                    erl_eval:'-inside-an-interpreted-fun-'"
2841    "({\"1\xc2\xaa\",170,<<\"hi\">>,\n                                    "
2842    "                        <<\"1\xc2\xaa\">>}) .\n" = t(Test10),
2843    Test11 =
2844        <<"io:setopts([{encoding,utf8}]).
2845           A = {\"1\\xaa\",
2846           $\\xaa,
2847           << <<\"hi\">>/binary >>,
2848           <<\"1\xaa\">>},
2849           fun(a) -> true end(A).">>,
2850
2851    "ok.\n** exception error: no function clause matching \n"
2852    "                    erl_eval:'-inside-an-interpreted-fun-'"
2853    "({\"1\xaa\",170,<<\"hi\">>,\n                                           "
2854    "                 <<\"1\xaa\"/utf8>>}) .\n"  = t({Node,Test11}),
2855    Test12 = <<"fun(a, b) -> false end(65, [1089]).">>,
2856    "** exception error: no function clause matching \n"
2857    "                    erl_eval:'-inside-an-interpreted-fun-'(65,[1089])"
2858    " .\n" = t(Test12),
2859    Test13 =
2860        <<"io:setopts([{encoding,utf8}]).
2861           fun(a, b) -> false end(65, [1089]).">>,
2862    "ok.\n** exception error: no function clause matching \n"
2863    "                    erl_eval:'-inside-an-interpreted-fun-'(65,\"\x{441}\")"
2864    " .\n" = t({Node,Test13}),
2865
2866    %% Unicode atoms.
2867    Test14 = <<"'\\x{447}\\x{435}'().">>,
2868    "** exception error: undefined shell command '\\x{447}\\x{435}'/0.\n" =
2869        t(Test14),
2870    Test15 = <<"io:setopts([{encoding,utf8}]).
2871                '\\x{447}\\x{435}'().">>,
2872    "ok.\n** exception error: undefined shell command '\x{447}\x{435}'/0.\n" =
2873        t({Node,Test15}),
2874    Test16 = <<"shell_SUITE:'\\x{447}\\x{435}'().">>,
2875    "** exception error: undefined function "
2876   "shell_SUITE:'\\x{447}\\x{435}'/0.\n" = t(Test16),
2877    Test17 = <<"io:setopts([{encoding,utf8}]).
2878                shell_SUITE:'\\x{447}\\x{435}'().">>,
2879    "ok.\n** exception error: undefined function "
2880    "shell_SUITE:'\x{447}\x{435}'/0.\n" =
2881        t({Node,Test17}),
2882    test_server:stop_node(Node),
2883    ok.
2884
2885otp_13719(Config) when is_list(Config) ->
2886    Test = <<"-module(otp_13719).
2887              -record(bar, {}).
2888              -record(foo, {bar :: #bar{}}).">>,
2889    File = filename("otp_13719.erl", Config),
2890    Beam = filename("otp_13719.beam", Config),
2891    ok = compile_file(Config, File, Test, []),
2892    RR = "rr(\"" ++ Beam ++ "\"). #foo{}.",
2893    "[bar,foo]\n#foo{bar = undefined}.\n" = t(RR),
2894    file:delete(filename("test.beam", Config)),
2895    file:delete(File),
2896    ok.
2897
2898otp_14285(Config) ->
2899    {ok,Node} = start_node(shell_suite_helper_4,
2900			   "-pa "++proplists:get_value(priv_dir,Config)++
2901			   " +pc unicode"),
2902    Test1 =
2903        <<"begin
2904               io:setopts([{encoding,utf8}]),
2905               [1024] = atom_to_list('\\x{400}'),
2906               rd('\\x{400}', {'\\x{400}' = '\\x{400}'}),
2907               ok = rl('\\x{400}')
2908           end.">>,
2909    "-record('\x{400}',{'\x{400}' = '\x{400}'}).\nok.\n" =
2910        t({Node,Test1}),
2911    test_server:stop_node(Node),
2912    ok.
2913
2914otp_14296(Config) when is_list(Config) ->
2915    fun() ->
2916            F = fun() -> a end,
2917            LocalFun = term_to_string(F),
2918            S = LocalFun ++ ".",
2919            "1: syntax error before: Fun" = comm_err(S)
2920    end(),
2921
2922    fun() ->
2923            F = fun mod:func/1,
2924            ExternalFun = term_to_string(F),
2925            S = ExternalFun ++ ".",
2926            R = ExternalFun ++ ".\n",
2927            R = t(S)
2928    end(),
2929
2930    fun() ->
2931            UnknownPid = "<100000.0.0>",
2932            S = UnknownPid ++ ".",
2933            "1: syntax error before: '<'" = comm_err(S)
2934    end(),
2935
2936    fun() ->
2937            KnownPid = term_to_string(self()),
2938            S = KnownPid ++ ".",
2939            R = KnownPid ++ ".\n",
2940            R = t(S)
2941    end(),
2942
2943    fun() ->
2944            Port = open_port({spawn, "ls"}, [{line,1}]),
2945            KnownPort = erlang:port_to_list(Port),
2946            S = KnownPort ++ ".",
2947            R = KnownPort ++ ".\n",
2948            R = t(S)
2949    end(),
2950
2951    fun() ->
2952            UnknownPort = "#Port<100000.0>",
2953            S = UnknownPort ++ ".",
2954            "1: syntax error before: Port" = comm_err(S)
2955    end(),
2956
2957    fun() ->
2958            UnknownRef = "#Ref<100000.0.0.0>",
2959            S = UnknownRef ++ ".",
2960            "1: syntax error before: Ref" = comm_err(S)
2961    end(),
2962
2963    fun() ->
2964            KnownRef = term_to_string(make_ref()),
2965            S = KnownRef ++ ".",
2966            R = KnownRef ++ ".\n",
2967            R = t(S)
2968    end(),
2969
2970    %% Test erl_eval:extended_parse_term/1
2971    TF = fun(S) ->
2972                 {ok, Ts, _} = erl_scan:string(S++".", 1, [text]),
2973                 case erl_eval:extended_parse_term(Ts) of
2974                     {ok, Term} -> Term;
2975                     {error, _}=Error -> Error
2976                 end
2977         end,
2978    Fun = fun m:f/1,
2979    Fun = TF(term_to_string(Fun)),
2980    Fun = TF("fun m:f/1"),
2981    Pid = self(),
2982    Pid = TF(term_to_string(Pid)),
2983    Ref = make_ref(),
2984    Ref = TF(term_to_string(Ref)),
2985    Term = {[10, a], {"foo", []}, #{x => <<"bar">>}},
2986    Term = TF(lists:flatten(io_lib:format("~p", [Term]))),
2987    {$a, F1, "foo"} = TF("{$a, 1.0, \"foo\"}"),
2988    true = is_float(F1),
2989    3 = TF("+3"),
2990    $a = TF("+$a"),
2991    true = is_float(TF("+1.0")),
2992    true  = -3 =:= TF("-3"),
2993    true = -$a =:= TF("-$a"),
2994    true = is_float(TF("-1.0")),
2995    {error, {_, _, ["syntax error"++_|_]}} = TF("{1"),
2996    {error, {_,_,"bad term"}} = TF("fun() -> foo end"),
2997    {error, {_,_,"bad term"}} = TF("1, 2"),
2998    ok.
2999
3000term_to_string(T) ->
3001    lists:flatten(io_lib:format("~w", [T])).
3002
3003scan(B) ->
3004    F = fun(Ts) ->
3005                case erl_parse:parse_term(Ts) of
3006                    {ok,Term} ->
3007                        Term;
3008                    _Error ->
3009                        {ok,Form} = erl_parse:parse_form(Ts),
3010                        Form
3011                end
3012        end,
3013    scan(t(B), F).
3014
3015scan(S0, F) ->
3016    case erl_scan:tokens([], S0, 1) of
3017        {done,{ok,Ts,_},S} ->
3018            [F(Ts) | scan(S, F)];
3019        _Else ->
3020            []
3021    end.
3022
3023t({Node,Bin,Enc}) when is_atom(Node),is_binary(Bin), is_atom(Enc) ->
3024    t0({Bin,Enc}, fun() -> start_new_shell(Node) end);
3025t({Node,Bin}) when is_atom(Node),is_binary(Bin) ->
3026    t0({Bin,latin1}, fun() -> start_new_shell(Node) end);
3027t(Bin) when is_binary(Bin) ->
3028    t0({Bin,latin1}, fun() -> start_new_shell() end);
3029t({Bin,Enc}) when is_binary(Bin), is_atom(Enc) ->
3030    t0({Bin,Enc}, fun() -> start_new_shell() end);
3031t(L) ->
3032    t(list_to_binary(L)).
3033
3034t0({Bin,Enc}, F) ->
3035    %% Spawn a process so that io_request messages do not interfer.
3036    P = self(),
3037    C = spawn(fun() -> t1(P, {Bin, Enc}, F) end),
3038    receive {C, R} -> R end.
3039
3040t1(Parent, {Bin,Enc}, F) ->
3041    io:format("*** Testing ~s~n", [binary_to_list(Bin)]),
3042    S = #state{bin = Bin, unic = Enc, reply = [], leader = group_leader()},
3043    group_leader(self(), self()),
3044    _Shell = F(),
3045    try
3046        server_loop(S)
3047    catch exit:R -> Parent ! {self(), R};
3048          throw:{?MODULE,LoopReply,latin1} ->
3049	    L0 = binary_to_list(list_to_binary(LoopReply)),
3050	    [$\n | L1] = lists:dropwhile(fun(X) -> X =/= $\n end, L0),
3051	    Parent ! {self(), dotify(L1)};
3052          throw:{?MODULE,LoopReply,_Uni} ->
3053	    Tmp = unicode:characters_to_binary(LoopReply),
3054	    L0 = unicode:characters_to_list(Tmp),
3055	    [$\n | L1] = lists:dropwhile(fun(X) -> X =/= $\n end, L0),
3056	    Parent ! {self(), dotify(L1)}
3057    after group_leader(S#state.leader, self())
3058    end.
3059
3060dotify([$., $\n | L]) ->
3061    [$., $\n | dotify(L)];
3062dotify([$,, $\n | L]) ->
3063    [$,, $\n | dotify(L)];
3064dotify("ok\n" ++ L) ->
3065    "ok.\n" ++ dotify(L);
3066dotify("\nok\n" ++ L) ->
3067    ".\nok.\n" ++ dotify(L);
3068dotify([$\n]) ->
3069    [$., $\n];
3070dotify([C | L]) ->
3071    [C | dotify(L)];
3072dotify([]) ->
3073    [].
3074
3075start_new_shell() ->
3076    Shell = shell:start(),
3077    link(Shell),
3078    Shell.
3079
3080start_new_shell(Node) ->
3081    Shell = rpc:call(Node,shell,start,[]),
3082    link(Shell),
3083    Shell.
3084
3085%% This is a very minimal implementation of the IO protocol...
3086
3087server_loop(S) ->
3088    receive
3089        {io_request, From, ReplyAs, Request} when is_pid(From) ->
3090	    server_loop(do_io_request(Request, From, S, ReplyAs));
3091	NotExpected ->
3092            exit(NotExpected)
3093    end.
3094
3095do_io_request(Req, From, S, ReplyAs) ->
3096    case io_requests([Req], [], S) of
3097        {_Status,{eof,_},S1} ->
3098	    io_reply(From, ReplyAs, {error,terminated}),
3099	    throw({?MODULE,S1#state.reply,S1#state.unic});
3100	{_Status,Reply,S1} ->
3101	    io_reply(From, ReplyAs, Reply),
3102	    S1
3103    end.
3104
3105io_reply(From, ReplyAs, Reply) ->
3106    From ! {io_reply, ReplyAs, Reply}.
3107
3108io_requests([{requests, Rs1} | Rs], Cont, S) ->
3109    io_requests(Rs1, [Rs | Cont], S);
3110io_requests([R | Rs], Cont, S) ->
3111    case io_request(R, S) of
3112        {ok, ok, S1} ->
3113            io_requests(Rs, Cont, S1);
3114        Reply ->
3115            Reply
3116    end;
3117io_requests([], [Rs|Cont], S) ->
3118    io_requests(Rs, Cont, S);
3119io_requests([], [], S) ->
3120    {ok,ok,S}.
3121
3122io_request({setopts, Opts}, S) ->
3123    #state{unic = OldEnc, bin = Bin} = S,
3124    NewEnc = case proplists:get_value(encoding, Opts) of
3125                 undefined -> OldEnc;
3126                 utf8 -> unicode;
3127                 New -> New
3128             end,
3129    NewBin = case {OldEnc, NewEnc} of
3130                 {E, E} -> Bin;
3131                 {latin1, _} ->
3132                     unicode:characters_to_binary(Bin, latin1, unicode);
3133                 {_, latin1} ->
3134                     unicode:characters_to_binary(Bin, unicode, latin1);
3135                 {_, _} -> Bin
3136             end,
3137    {ok, ok, S#state{unic = NewEnc, bin = NewBin}};
3138io_request(getopts, S) ->
3139    {ok,[{encoding,S#state.unic}],S};
3140io_request({get_geometry,columns}, S) ->
3141    {ok,80,S};
3142io_request({get_geometry,rows}, S) ->
3143    {ok,24,S};
3144io_request({put_chars,Chars}, S) ->
3145    {ok,ok,S#state{reply = [S#state.reply | Chars]}};
3146io_request({put_chars,latin1,Chars}, S) ->
3147    {ok,ok,S#state{reply = [S#state.reply | Chars]}};
3148io_request({put_chars,unicode,Chars0}, S) ->
3149    Chars = unicode:characters_to_list(Chars0),
3150    {ok,ok,S#state{reply = [S#state.reply | Chars]}};
3151io_request({put_chars,Mod,Func,Args}, S) ->
3152    case catch apply(Mod, Func, Args) of
3153        Chars when is_list(Chars) ->
3154            io_request({put_chars,Chars}, S)
3155    end;
3156io_request({put_chars,Enc,Mod,Func,Args}, S) ->
3157    case catch apply(Mod, Func, Args) of
3158        Chars when is_list(Chars) ->
3159            io_request({put_chars,Enc,Chars}, S)
3160    end;
3161io_request({get_until,_Prompt,Mod,Func,ExtraArgs}, S) ->
3162    get_until(Mod, Func, ExtraArgs, S, latin1);
3163io_request({get_until,Enc,_Prompt,Mod,Func,ExtraArgs}, S) ->
3164    get_until(Mod, Func, ExtraArgs, S, Enc).
3165
3166get_until(Mod, Func, ExtraArgs, S, Enc) ->
3167    get_until_loop(Mod, Func, ExtraArgs, S, {more,[]}, Enc).
3168
3169get_until_loop(M, F, As, S, {more,Cont}, Enc) ->
3170    Bin = S#state.bin,
3171    case byte_size(Bin) of
3172        0 ->
3173            get_until_loop(M, F, As, S,
3174                           catch apply(M, F, [Cont,eof|As]), Enc);
3175	_ when S#state.unic =:= latin1 ->
3176	    get_until_loop(M, F, As, S#state{bin = <<>>},
3177			   catch apply(M, F, [Cont,binary_to_list(Bin)|As]), Enc);
3178	_ ->
3179	    get_until_loop(M, F, As, S#state{bin = <<>>},
3180			   catch apply(M, F, [Cont,unicode:characters_to_list(Bin)|As]), Enc)
3181    end;
3182get_until_loop(_M, _F, _As, S, {done,Res,Buf}, Enc) ->
3183    {ok,Res,S#state{bin = buf2bin(Buf, Enc)}};
3184get_until_loop(_M, F, _As, S, _Other, _Enc) ->
3185    {error,{error,F},S}.
3186
3187buf2bin(eof,_) ->
3188    <<>>;
3189buf2bin(Buf,latin1) ->
3190    list_to_binary(Buf);
3191buf2bin(Buf,utf8) ->
3192    unicode:characters_to_binary(Buf,unicode,unicode);
3193buf2bin(Buf,unicode) ->
3194    unicode:characters_to_binary(Buf,unicode,unicode).
3195
3196run_file(Config, Module, Test) ->
3197    FileName = filename(lists:concat([Module, ".erl"]), Config),
3198    BeamFile = filename(lists:concat([Module, ".beam"]), Config),
3199    LoadBeamFile = filename(Module, Config),
3200    ok = file:write_file(FileName, Test),
3201    ok = compile_file(Config, FileName, Test, []),
3202    code:purge(Module),
3203    {module, Module} = code:load_abs(LoadBeamFile),
3204    ok = Module:t(),
3205    file:delete(FileName),
3206    file:delete(BeamFile),
3207    ok.
3208
3209compile_file(Config, File, Test, Opts0) ->
3210    Opts = [export_all,nowarn_export_all,return,{outdir,proplists:get_value(priv_dir, Config)}|Opts0],
3211    ok = file:write_file(File, Test),
3212    case compile:file(File, Opts) of
3213              {ok, _M, _Ws} -> ok;
3214              _ -> error
3215          end.
3216
3217filename(Name, Config) when is_atom(Name) ->
3218    filename(atom_to_list(Name), Config);
3219filename(Name, Config) ->
3220    filename:join(proplists:get_value(priv_dir, Config), Name).
3221
3222start_node(Name, Xargs) ->
3223    N = test_server:start_node(Name, slave, [{args, " " ++ Xargs}]),
3224    global:sync(),
3225    N.
3226
3227