~ubuntu-branches/ubuntu/lucid/erlang/lucid-updates

« back to all changes in this revision

Viewing changes to lib/stdlib/test/erl_eval_SUITE.erl

  • Committer: Elliot Murphy
  • Date: 2009-12-22 02:56:21 UTC
  • mfrom: (3.3.5 sid)
  • Revision ID: elliot@elliotmurphy.com-20091222025621-qv3rja8gbpiabkbe
Tags: 1:13.b.3-dfsg-2ubuntu1
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
* Fixed dialyzer(1) manpage which was placed into section 3 and conflicted
  with dialyzer(3erl).
* New upstream release (it adds a new binary package erlang-erl-docgen).
* Refreshed patches, removed most of emacs.patch which is applied upstream.
* Linked run_test binary from erlang-common-test package to /usr/bin.
* Fixed VCS headers in debian/control.
* Moved from prebuilt manpages to generated from sources. This adds
  erlang-manpages binary package and xsltproc build dependency.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
 
 
19
-module(erl_eval_SUITE).
 
20
-export([all/1]).
 
21
 
 
22
-export([guard_1/1, guard_2/1,
 
23
         match_pattern/1,
 
24
         match_bin/1,
 
25
         string_plusplus/1,
 
26
         pattern_expr/1,
 
27
         guard_3/1, guard_4/1,
 
28
         lc/1,
 
29
         simple_cases/1,
 
30
         unary_plus/1,
 
31
         apply_atom/1,
 
32
         otp_5269/1,
 
33
         otp_6539/1,
 
34
         otp_6543/1,
 
35
         otp_6787/1,
 
36
         otp_6977/1,
 
37
         otp_7550/1,
 
38
         otp_8133/1,
 
39
         funs/1,
 
40
         try_catch/1,
 
41
         eval_expr_5/1]).
 
42
 
 
43
%%
 
44
%% Define to run outside of test server
 
45
%%
 
46
%%-define(STANDALONE,1).
 
47
 
 
48
-import(lists,[concat/1, sort/1]).
 
49
 
 
50
-export([count_down/2, count_down_fun/0, do_apply/2, 
 
51
         local_func/3, local_func_value/2]).
 
52
 
 
53
-ifdef(STANDALONE).
 
54
-define(config(A,B),config(A,B)).
 
55
-export([config/2]).
 
56
-define(line, noop, ).
 
57
config(priv_dir,_) ->
 
58
    ".".
 
59
-else.
 
60
-include("test_server.hrl").
 
61
-export([init_per_testcase/2, fin_per_testcase/2]).
 
62
% Default timetrap timeout (set in init_per_testcase).
 
63
-define(default_timeout, ?t:minutes(1)).
 
64
init_per_testcase(_Case, Config) ->
 
65
    ?line Dog = ?t:timetrap(?default_timeout),
 
66
    [{watchdog, Dog} | Config].
 
67
fin_per_testcase(_Case, Config) ->
 
68
    Dog = ?config(watchdog, Config),
 
69
    test_server:timetrap_cancel(Dog),
 
70
    ok.
 
71
-endif.
 
72
 
 
73
all(doc) ->
 
74
    ["Test cases for the 'erl_eval' module."];
 
75
all(suite) ->
 
76
    [guard_1, guard_2, match_pattern, string_plusplus, pattern_expr,
 
77
     match_bin, guard_3, guard_4, 
 
78
     lc, simple_cases, unary_plus, apply_atom, otp_5269, otp_6539, otp_6543,
 
79
     otp_6787, otp_6977, otp_7550, otp_8133, funs, try_catch, eval_expr_5].
 
80
 
 
81
guard_1(doc) ->
 
82
    ["(OTP-2405)"];
 
83
guard_1(suite) ->
 
84
    [];
 
85
guard_1(Config) when is_list(Config) ->
 
86
    ?line {ok,Tokens ,_} =
 
87
        erl_scan:string("if a+4 == 4 -> yes; true -> no end. "),
 
88
    ?line {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
 
89
    ?line no = guard_1_compiled(),
 
90
    ?line {value, no, []} = erl_eval:expr(Expr, []),
 
91
    ok.
 
92
 
 
93
guard_1_compiled() ->
 
94
    if a+4 == 4 -> yes; true -> no end.
 
95
 
 
96
guard_2(doc) ->
 
97
    ["Similar to guard_1, but type-correct"];
 
98
guard_2(suite) ->
 
99
    [];
 
100
guard_2(Config) when is_list(Config) ->
 
101
    ?line {ok,Tokens ,_} =
 
102
        erl_scan:string("if 6+4 == 4 -> yes; true -> no end. "),
 
103
    ?line {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
 
104
    ?line no = guard_2_compiled(),
 
105
    ?line {value, no, []} = erl_eval:expr(Expr, []),
 
106
    ok.
 
107
 
 
108
guard_2_compiled() ->
 
109
    if 6+4 == 4 -> yes; true -> no end.
 
110
 
 
111
string_plusplus(doc) ->
 
112
    ["OTP-3069: syntactic sugar string ++ ..."];
 
113
string_plusplus(suite) ->
 
114
    [];
 
115
string_plusplus(Config) when is_list(Config) ->
 
116
    ?line check(fun() -> case "abc" of "ab" ++ L -> L end end,
 
117
                "case \"abc\" of \"ab\" ++ L -> L end. ",
 
118
                "c"),
 
119
    ?line check(fun() -> case "abcde" of "ab" ++ "cd" ++ L -> L end end,
 
120
                "case \"abcde\" of \"ab\" ++ \"cd\" ++ L -> L end. ",
 
121
                "e"),
 
122
    ?line check(fun() -> case "abc" of [97, 98] ++ L -> L end end,
 
123
                "case \"abc\" of [97, 98] ++ L -> L end. ",
 
124
                "c"),
 
125
    ok.
 
126
 
 
127
match_pattern(doc) ->
 
128
    ["OTP-2983: match operator in pattern"];
 
129
match_pattern(suite) ->
 
130
    [];
 
131
match_pattern(Config) when is_list(Config) ->
 
132
    ?line check(fun() -> case {a, b} of {a, _X}=Y -> {x,Y} end end,
 
133
                "case {a, b} of {a, X}=Y -> {x,Y} end. ",
 
134
                {x, {a, b}}),
 
135
    ?line check(fun() -> case {a, b} of Y={a, _X} -> {x,Y} end end,
 
136
                "case {a, b} of Y={a, X} -> {x,Y} end. ",
 
137
                {x, {a, b}}),
 
138
    ?line check(fun() -> case {a, b} of Y={a, _X}=Z -> {Z,Y} end end,
 
139
                "case {a, b} of Y={a, X}=Z -> {Z,Y} end. ",
 
140
                {{a, b}, {a, b}}),
 
141
    ?line check(fun() -> A = 4, B = 28, <<13:(A+(X=B))>>, X end,
 
142
                "begin A = 4, B = 28, <<13:(A+(X=B))>>, X end.",
 
143
                28),
 
144
    ok.
 
145
 
 
146
match_bin(doc) ->
 
147
    ["binary match problems"];
 
148
match_bin(suite) ->
 
149
    [];
 
150
match_bin(Config) when is_list(Config) ->
 
151
    ?line check(fun() -> <<"abc">> = <<"abc">> end,
 
152
                "<<\"abc\">> = <<\"abc\">>. ",
 
153
                <<"abc">>),
 
154
    ?line check(fun() ->
 
155
                        <<Size,B:Size/binary,Rest/binary>> = <<2,"AB","CD">>,
 
156
                        {Size,B,Rest}
 
157
                end,
 
158
                "begin <<Size,B:Size/binary,Rest/binary>> = <<2,\"AB\",\"CD\">>, "
 
159
                "{Size,B,Rest} end. ",
 
160
                {2,<<"AB">>,<<"CD">>}),
 
161
    ok.
 
162
 
 
163
pattern_expr(doc) ->
 
164
    ["OTP-3144: compile-time expressions in pattern"];
 
165
pattern_expr(suite) ->
 
166
    [];
 
167
pattern_expr(Config) when is_list(Config) ->
 
168
    ?line check(fun() -> case 4 of 2+2 -> ok end end,
 
169
                "case 4 of 2+2 -> ok end. ",
 
170
                ok),
 
171
    ?line check(fun() -> case 2 of +2 -> ok end end,
 
172
                "case 2 of +2 -> ok end. ",
 
173
                ok),
 
174
    ok.
 
175
 
 
176
guard_3(doc) ->
 
177
    ["OTP-4518."];
 
178
guard_3(suite) ->
 
179
    [];
 
180
guard_3(Config) when is_list(Config) ->
 
181
    ?line check(fun() -> if false -> false; true -> true end end,
 
182
                "if false -> false; true -> true end.",
 
183
                true),
 
184
    ?line check(fun() -> if <<"hej">> == <<"hopp">> -> true; 
 
185
                            true -> false end end,
 
186
                "begin if <<\"hej\">> == <<\"hopp\">> -> true; 
 
187
                          true -> false end end.",
 
188
                false),
 
189
    ?line check(fun() -> if <<"hej">> == <<"hej">> -> true; 
 
190
                            true -> false end end,
 
191
                "begin if <<\"hej\">> == <<\"hej\">> -> true; 
 
192
                          true -> false end end.",
 
193
                true),
 
194
    ok.
 
195
 
 
196
guard_4(doc) ->
 
197
    ["OTP-4885."];
 
198
guard_4(suite) ->
 
199
    [];
 
200
guard_4(Config) when is_list(Config) ->
 
201
    ?line check(fun() -> if {erlang,'+'}(3,a) -> true ; true -> false end end,
 
202
                "if {erlang,'+'}(3,a) -> true ; true -> false end.",
 
203
                false),
 
204
    ?line check(fun() -> if {erlang,is_integer}(3) -> true ; true -> false end
 
205
                end,
 
206
                "if {erlang,is_integer}(3) -> true ; true -> false end.",
 
207
                true),
 
208
    ?line check(fun() -> [X || X <- [1,2,3], erlang:is_integer(X)] end,
 
209
                "[X || X <- [1,2,3], erlang:is_integer(X)].",
 
210
                [1,2,3]),
 
211
    ?line check(fun() -> if is_atom(is_integer(a)) -> true ; true -> false end
 
212
                end,
 
213
                "if is_atom(is_integer(a)) -> true ; true -> false end.",
 
214
                true),
 
215
    ?line check(fun() -> if {erlang,is_atom}({erlang,is_integer}(a)) -> true;
 
216
                            true -> false end end,
 
217
                "if {erlang,is_atom}({erlang,is_integer}(a)) -> true; "
 
218
                "true -> false end.",
 
219
                true),
 
220
    ?line check(fun() -> if is_atom(3+a) -> true ; true -> false end end,
 
221
                "if is_atom(3+a) -> true ; true -> false end.",
 
222
                false),
 
223
    ?line check(fun() -> if erlang:is_atom(3+a) -> true ; true -> false end 
 
224
                end,
 
225
                "if erlang:is_atom(3+a) -> true ; true -> false end.",
 
226
                false),
 
227
    ok.
 
228
 
 
229
 
 
230
lc(doc) ->
 
231
    ["OTP-4518."];
 
232
lc(suite) ->
 
233
    [];
 
234
lc(Config) when is_list(Config) ->
 
235
    ?line check(fun() -> X = 32, [X || X <- [1,2,3]] end,
 
236
                "begin X = 32, [X || X <- [1,2,3]] end.",
 
237
                [1,2,3]),
 
238
    ?line check(fun() -> X = 32, 
 
239
                         [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end,
 
240
    %% "binsize variable"          ^
 
241
                "begin X = 32, 
 
242
                 [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end.",
 
243
                [1,2]),
 
244
    ?line check(fun() -> Y = 13,[X || {X,Y} <- [{1,2}]] end,
 
245
                "begin Y = 13,[X || {X,Y} <- [{1,2}]] end.",
 
246
                [1]),
 
247
    ?line error_check("begin [A || X <- [{1,2}], 1 == A] end.",
 
248
                      {unbound_var,'A'}),
 
249
    ?line error_check("begin X = 32, 
 
250
                        [{Y,W} || X <- [1,2,32,Y=4], Z <- [1,2,W=3]] end.",
 
251
                      {unbound_var,'Y'}),
 
252
    ?line error_check("begin X = 32,<<A:B>> = <<100:X>> end.",
 
253
                      {unbound_var,'B'}),
 
254
    ?line check(fun() -> [X || X <- [1,2,3,4], not (X < 2)] end,
 
255
                "begin [X || X <- [1,2,3,4], not (X < 2)] end.",
 
256
                [2,3,4]),
 
257
    ?line check(fun() -> [X || X <- [true,false], X] end,
 
258
                "[X || X <- [true,false], X].", [true]),
 
259
    ok.
 
260
 
 
261
simple_cases(doc) ->
 
262
    ["Simple cases, just to cover some code."];
 
263
simple_cases(suite) ->
 
264
    [];
 
265
simple_cases(Config) when is_list(Config) ->
 
266
    ?line check(fun() -> A = $C end, "A = $C.", $C),
 
267
    %% ?line check(fun() -> A = 3.14 end, "A = 3.14.", 3.14),
 
268
    ?line check(fun() -> self() ! a, A = receive a -> true end end,
 
269
                "begin self() ! a, A = receive a -> true end end.",
 
270
                true),
 
271
    ?line check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
 
272
                         receive b -> b end, 
 
273
                         {messages, [a,c]} =
 
274
                             erlang:process_info(self(), messages),
 
275
                         c:flush() end,
 
276
                "begin c:flush(), self() ! a, self() ! b, self() ! c,"
 
277
                "receive b -> b end,"
 
278
                "{messages, [a,c]} ="
 
279
                "     erlang:process_info(self(), messages), c:flush() end.",
 
280
                ok),
 
281
    ?line check(fun() -> self() ! a, A = receive a -> true 
 
282
                                         after 0 -> false end end,
 
283
                "begin self() ! a, A = receive a -> true"
 
284
                "                      after 0 -> false end end.",
 
285
                true),
 
286
    ?line check(fun() -> c:flush(), self() ! a, self() ! b, self() ! c,
 
287
                         receive b -> b after 0 -> true end, 
 
288
                         {messages, [a,c]} =
 
289
                             erlang:process_info(self(), messages),
 
290
                         c:flush() end,
 
291
                "begin c:flush(), self() ! a, self() ! b, self() ! c,"
 
292
                "receive b -> b after 0 -> true end,"
 
293
                "{messages, [a,c]} ="
 
294
                "     erlang:process_info(self(), messages), c:flush() end.",
 
295
                ok),
 
296
    ?line check(fun() -> receive _ -> true after 10 -> false end end,
 
297
                "receive _ -> true after 10 -> false end.",
 
298
                false),
 
299
    ?line check(fun() -> F = fun(A) -> A end, true = 3 == F(3) end,
 
300
                "begin F = fun(A) -> A end, true = 3 == F(3) end.",
 
301
                true),
 
302
    ?line check(fun() -> F = fun(A) -> A end, true = 3 == apply(F, [3]) end,
 
303
                "begin F = fun(A) -> A end, true = 3 == apply(F,[3]) end.",
 
304
                true),
 
305
    ?line check(fun() -> catch throw(a) end, "catch throw(a).", a),
 
306
    ?line check(fun() -> catch a end, "catch a.", a),
 
307
    ?line check(fun() -> 4 == 3 end, "4 == 3.", false),
 
308
    ?line check(fun() -> not true end, "not true.", false),
 
309
    ?line check(fun() -> -3 end, "-3.", -3),
 
310
 
 
311
    ?line error_check("3.0 = 4.0.", {badmatch,4.0}),
 
312
    ?line check(fun() -> <<(3.0+2.0):32/float>> = <<5.0:32/float>> end,
 
313
                "<<(3.0+2.0):32/float>> = <<5.0:32/float>>.",
 
314
                <<5.0:32/float>>),
 
315
 
 
316
    ?line check(fun() -> false andalso kludd end, "false andalso kludd.",
 
317
                false),
 
318
    ?line check(fun() -> true andalso true end, "true andalso true.",
 
319
                true),
 
320
    ?line check(fun() -> true andalso false end, "true andalso false.",
 
321
                false),
 
322
    ?line check(fun() -> true andalso kludd end, "true andalso kludd.",
 
323
                kludd),
 
324
    ?line error_check("kladd andalso kludd.", {badarg,kladd}),
 
325
 
 
326
    ?line check(fun() -> if false andalso kludd -> a; true -> b end end,
 
327
                "if false andalso kludd -> a; true -> b end.",
 
328
                b),
 
329
    ?line check(fun() -> if true andalso true -> a; true -> b end end, 
 
330
                "if true andalso true -> a; true -> b end.",
 
331
                a),
 
332
    ?line check(fun() -> if true andalso false -> a; true -> b end end, 
 
333
                "if true andalso false -> a; true -> b end.",
 
334
                b),
 
335
 
 
336
    ?line check(fun() -> true orelse kludd end, 
 
337
                "true orelse kludd.", true),
 
338
    ?line check(fun() -> false orelse false end, 
 
339
                "false orelse false.", false),
 
340
    ?line check(fun() -> false orelse true end, 
 
341
                "false orelse true.", true),
 
342
    ?line check(fun() -> false orelse kludd end, 
 
343
                "false orelse kludd.", kludd),
 
344
    ?line error_check("kladd orelse kludd.", {badarg,kladd}),
 
345
    ?line error_check("[X || X <- [1,2,3], begin 1 end].",{bad_filter,1}),
 
346
    ?line error_check("[X || X <- a].",{bad_generator,a}),
 
347
 
 
348
    ?line check(fun() -> if true orelse kludd -> a; true -> b end end, 
 
349
                "if true orelse kludd -> a; true -> b end.", a),
 
350
    ?line check(fun() -> if false orelse false -> a; true -> b end end, 
 
351
                "if false orelse false -> a; true -> b end.", b),
 
352
    ?line check(fun() -> if false orelse true -> a; true -> b end end, 
 
353
                "if false orelse true -> a; true -> b end.", a),
 
354
 
 
355
    ?line check(fun() -> [X || X <- [1,2,3], X+2] end,
 
356
                "[X || X <- [1,2,3], X+2].", []),
 
357
 
 
358
    ?line check(fun() -> [X || X <- [1,2,3], [X] == [X || X <- [2]]] end,
 
359
                "[X || X <- [1,2,3], [X] == [X || X <- [2]]].",
 
360
                [2]),
 
361
    ?line check(fun() -> F = fun(1) -> ett; (2) -> zwei end, 
 
362
                         ett = F(1), zwei = F(2) end,
 
363
                "begin F = fun(1) -> ett; (2) -> zwei end, 
 
364
                         ett = F(1), zwei = F(2) end.",
 
365
                zwei),
 
366
    ?line check(fun() -> F = fun(X) when X == 1 -> ett; 
 
367
                                (X) when X == 2 -> zwei end, 
 
368
                         ett = F(1), zwei = F(2) end,
 
369
                "begin F = fun(X) when X == 1 -> ett; 
 
370
                              (X) when X == 2 -> zwei end, 
 
371
                         ett = F(1), zwei = F(2) end.",
 
372
                zwei),
 
373
    ?line error_check("begin F = fun(1) -> ett end, zwei = F(2) end.",
 
374
                      function_clause),
 
375
    ?line check(fun() -> if length([1]) == 1 -> yes; 
 
376
                            true -> no end end,
 
377
                "if length([1]) == 1 -> yes; 
 
378
                            true -> no end.",
 
379
                yes),
 
380
    ?line check(fun() -> if is_integer(3) -> true; true -> false end end,
 
381
                "if is_integer(3) -> true; true -> false end.", true),
 
382
    ?line check(fun() -> if integer(3) -> true; true -> false end end,
 
383
                "if integer(3) -> true; true -> false end.", true),
 
384
    ?line check(fun() -> if is_float(3) -> true; true -> false end end,
 
385
                "if is_float(3) -> true; true -> false end.", false),
 
386
    ?line check(fun() -> if float(3) -> true; true -> false end end,
 
387
                "if float(3) -> true; true -> false end.", false),
 
388
    ?line check(fun() -> if is_number(3) -> true; true -> false end end,
 
389
                "if is_number(3) -> true; true -> false end.", true),
 
390
    ?line check(fun() -> if number(3) -> true; true -> false end end,
 
391
                "if number(3) -> true; true -> false end.", true),
 
392
    ?line check(fun() -> if is_atom(a) -> true; true -> false end end,
 
393
                "if is_atom(a) -> true; true -> false end.", true),
 
394
    ?line check(fun() -> if atom(a) -> true; true -> false end end,
 
395
                "if atom(a) -> true; true -> false end.", true),
 
396
    ?line check(fun() -> if is_list([]) -> true; true -> false end end,
 
397
                "if is_list([]) -> true; true -> false end.", true),
 
398
    ?line check(fun() -> if list([]) -> true; true -> false end end,
 
399
                "if list([]) -> true; true -> false end.", true),
 
400
    ?line check(fun() -> if is_tuple({}) -> true; true -> false end end,
 
401
                "if is_tuple({}) -> true; true -> false end.", true),
 
402
    ?line check(fun() -> if tuple({}) -> true; true -> false end end,
 
403
                "if tuple({}) -> true; true -> false end.", true),
 
404
    ?line check(fun() -> if is_pid(self()) -> true; true -> false end end,
 
405
                "if is_pid(self()) -> true; true -> false end.", true),
 
406
    ?line check(fun() -> if pid(self()) -> true; true -> false end end,
 
407
                "if pid(self()) -> true; true -> false end.", true),
 
408
    ?line check(fun() -> R = make_ref(), if is_reference(R) -> true; 
 
409
                                            true -> false end end,
 
410
                "begin R = make_ref(), if is_reference(R) -> true;"
 
411
                "true -> false end end.", true),
 
412
    ?line check(fun() -> R = make_ref(), if reference(R) -> true; 
 
413
                                            true -> false end end,
 
414
                "begin R = make_ref(), if reference(R) -> true;"
 
415
                "true -> false end end.", true),
 
416
    ?line check(fun() -> if is_port(a) -> true; true -> false end end,
 
417
                "if is_port(a) -> true; true -> false end.", false),
 
418
    ?line check(fun() -> if port(a) -> true; true -> false end end,
 
419
                "if port(a) -> true; true -> false end.", false),
 
420
    ?line check(fun() -> if is_function(a) -> true; true -> false end end,
 
421
                "if is_function(a) -> true; true -> false end.", false),
 
422
    ?line check(fun() -> if function(a) -> true; true -> false end end,
 
423
                "if function(a) -> true; true -> false end.", false),
 
424
    ?line check(fun() -> if is_binary(<<>>) -> true; true -> false end end,
 
425
                "if is_binary(<<>>) -> true; true -> false end.", true),
 
426
    ?line check(fun() -> if binary(<<>>) -> true; true -> false end end,
 
427
                "if binary(<<>>) -> true; true -> false end.", true),
 
428
    ?line check(fun() -> if is_integer(a) == true -> yes; 
 
429
                            true -> no end end,
 
430
                "if is_integer(a) == true -> yes; 
 
431
                            true -> no end.",
 
432
                no),
 
433
    ?line check(fun() -> if [] -> true; true -> false end end,
 
434
                "if [] -> true; true -> false end.", false),
 
435
    ?line error_check("if lists:member(1,[1]) -> true; true -> false end.",
 
436
                      illegal_guard_expr),
 
437
    ?line error_check("if false -> true end.", if_clause),
 
438
    ?line check(fun() -> if a+b -> true; true -> false end end,
 
439
                "if a + b -> true; true -> false end.", false),
 
440
    ?line check(fun() -> if + b -> true; true -> false end end,
 
441
                "if + b -> true; true -> false end.", false),
 
442
    ?line error_check("case foo of bar -> true end.", {case_clause,foo}),
 
443
    ?line error_check("case 4 of 2+a -> true; _ -> false end.", 
 
444
                      illegal_pattern),
 
445
    ?line error_check("case 4 of +a -> true; _ -> false end.", 
 
446
                      illegal_pattern),
 
447
    ?line check(fun() -> case a of 
 
448
                             X when X == b -> one;
 
449
                             X when X == a -> two
 
450
                         end end,
 
451
                "begin case a of 
 
452
                             X when X == b -> one;
 
453
                             X when X == a -> two
 
454
                         end end.", two),
 
455
    ?line error_check("3 = 4.", {badmatch,4}),
 
456
    ?line error_check("a = 3.", {badmatch,3}),
 
457
    %% ?line error_check("3.1 = 2.7.",{badmatch,2.7}),
 
458
    ?line error_check("$c = 4.", {badmatch,4}),
 
459
    ?line check(fun() -> $c = $c end, "$c = $c.", $c),
 
460
    ?line check(fun() -> _ = bar end, "_ = bar.", bar),
 
461
    ?line check(fun() -> A = 14, A = 14 end, 
 
462
                "begin A = 14, A = 14 end.", 14),
 
463
    ?line error_check("begin A = 14, A = 16 end.", {badmatch,16}),
 
464
    ?line error_check("\"hej\" = \"san\".", {badmatch,"san"}),
 
465
    ?line check(fun() -> "hej" = "hej" end,
 
466
                "\"hej\" = \"hej\".", "hej"),
 
467
    ?line error_check("[] = [a].", {badmatch,[a]}),
 
468
    ?line check(fun() -> [] = [] end, "[] = [].", []),
 
469
    ?line error_check("[a] = [].", {badmatch,[]}),
 
470
    ?line error_check("{a,b} = 34.", {badmatch,34}),
 
471
    ?line check(fun() -> <<X:7>> = <<8:7>>, X end,
 
472
                "begin <<X:7>> = <<8:7>>, X end.", 8),
 
473
    ?line error_check("<<34:32>> = \"hej\".", {badmatch,"hej"}),
 
474
    ?line check(fun() -> trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end,
 
475
                "begin trunc((1 * 3 div 3 + 4 - 3) / 1) rem 2 end.", 0),
 
476
    ?line check(fun() -> (2#101 band 2#10101) bor (2#110 bxor 2#010) end,
 
477
                "(2#101 band 2#10101) bor (2#110 bxor 2#010).", 5),
 
478
    ?line check(fun() -> (2#1 bsl 4) + (2#10000 bsr 3) end,
 
479
                "(2#1 bsl 4) + (2#10000 bsr 3).", 18),
 
480
    ?line check(fun() -> ((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2) end,
 
481
                "((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2).", false),
 
482
    ?line check(fun() -> (a /= b) or (2 > 4) or (3 >= 3) end,
 
483
                "(a /= b) or (2 > 4) or (3 >= 3).", true),
 
484
    ?line check(fun() -> "hej" ++ "san" =/= "hejsan" -- "san" end,
 
485
                "\"hej\" ++ \"san\" =/= \"hejsan\" -- \"san\".", true),
 
486
    ?line check(fun() -> (bnot 1) < -0 end, "(bnot (+1)) < -0.", true),
 
487
    ok.
 
488
 
 
489
unary_plus(doc) ->
 
490
    ["OTP-4929. Unary plus rejects non-numbers."];
 
491
unary_plus(suite) ->
 
492
    [];
 
493
unary_plus(Config) when is_list(Config) ->
 
494
    ?line check(fun() -> F = fun(X) -> + X end, 
 
495
                         true = -1 == F(-1) end,
 
496
                "begin F = fun(X) -> + X end," 
 
497
                "      true = -1 == F(-1) end.", true, ['F'], none, none),
 
498
    ?line error_check("+a.", badarith),
 
499
    ok.
 
500
 
 
501
apply_atom(doc) ->
 
502
    ["OTP-5064. Can no longer apply atoms."];
 
503
apply_atom(suite) ->
 
504
    [];
 
505
apply_atom(Config) when is_list(Config) ->
 
506
    ?line error_check("[X || X <- [[1],[2]], 
 
507
                             begin L = length, L(X) =:= 1 end].", 
 
508
                      {badfun,length}),
 
509
    ok.
 
510
 
 
511
otp_5269(doc) ->
 
512
    ["OTP-5269. Bugs in the bit syntax."];
 
513
otp_5269(suite) ->
 
514
    [];
 
515
otp_5269(Config) when is_list(Config) ->
 
516
    ?line check(fun() -> L = 8,
 
517
                         F = fun(<<A:L,B:A>>) -> B end,
 
518
                         F(<<16:8, 7:16>>)
 
519
                end,
 
520
                "begin 
 
521
                   L = 8, F = fun(<<A:L,B:A>>) -> B end, F(<<16:8, 7:16>>)
 
522
                 end.",
 
523
                7),
 
524
    ?line check(fun() -> L = 8,
 
525
                         F = fun(<<L:L,B:L>>) -> B end,
 
526
                         F(<<16:8, 7:16>>)
 
527
                end,
 
528
                "begin 
 
529
                   L = 8, F = fun(<<L:L,B:L>>) -> B end, F(<<16:8, 7:16>>)
 
530
                 end.",
 
531
                7),
 
532
    ?line check(fun() -> L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end,
 
533
                "begin L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end.",
 
534
                7),
 
535
    ?line error_check("begin L = 8, <<L:L,B:L>> = <<16:8, 7:16>> end.",
 
536
                      {badmatch,<<16:8,7:16>>}),
 
537
    
 
538
    ?line error_check("begin <<L:16,L:L>> = <<16:16,8:16>>, L end.",
 
539
                      {badmatch, <<16:16,8:16>>}),
 
540
    ?line check(fun() -> U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end,
 
541
                "begin U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end.",
 
542
                32),
 
543
    ?line check(fun() -> U = 8, [U || <<U:U>> <- [<<32:8>>]] end,
 
544
                "begin U = 8, [U || <<U:U>> <- [<<32:8>>]] end.",
 
545
                [32]),
 
546
    ?line error_check("(fun({3,<<A:32,A:32>>}) -> a end)
 
547
                          ({3,<<17:32,19:32>>}).",
 
548
                      function_clause),
 
549
    ?line check(fun() -> [X || <<A:8,
 
550
                                 B:A>> <- [<<16:8,19:16>>],
 
551
                               <<X:8>> <- [<<B:8>>]] end,
 
552
                "[X || <<A:8,
 
553
                                 B:A>> <- [<<16:8,19:16>>],
 
554
                               <<X:8>> <- [<<B:8>>]].",
 
555
                [19]),
 
556
    ok.
 
557
 
 
558
otp_6539(doc) ->
 
559
    ["OTP-6539. try/catch bugs."];
 
560
otp_6539(suite) ->
 
561
    [];
 
562
otp_6539(Config) when is_list(Config) ->
 
563
    ?line check(fun() -> 
 
564
                        F = fun(A,B) -> 
 
565
                                    try A+B 
 
566
                                    catch _:_ -> dontthinkso 
 
567
                                    end 
 
568
                            end,
 
569
                        lists:zipwith(F, [1,2], [2,3])
 
570
                end,
 
571
                "begin 
 
572
                     F = fun(A,B) -> 
 
573
                                 try A+B 
 
574
                                 catch _:_ -> dontthinkso 
 
575
                                 end 
 
576
                         end,
 
577
                     lists:zipwith(F, [1,2], [2,3])
 
578
                 end.",
 
579
                [3, 5]),
 
580
    ok.
 
581
 
 
582
otp_6543(doc) ->
 
583
    ["OTP-6543. bitlevel binaries."];
 
584
otp_6543(suite) ->
 
585
    [];
 
586
otp_6543(Config) when is_list(Config) ->
 
587
    ?line check(fun() ->
 
588
                        << <<X>> || <<X>> <- [1,2,3] >>
 
589
                end,
 
590
                "<< <<X>> || <<X>> <- [1,2,3] >>.",
 
591
                <<>>),
 
592
    ?line check(fun() -> 
 
593
                        << <<X>> || X <- [1,2,3] >>
 
594
                end,
 
595
                "<< <<X>> || X <- [1,2,3] >>.",
 
596
                <<1,2,3>>),
 
597
    ?line check(fun() -> 
 
598
                        << <<X:8>> || <<X:2>> <= <<"hej">> >>
 
599
                end,
 
600
                "<< <<X:8>> || <<X:2>> <= <<\"hej\">> >>.",
 
601
                <<1,2,2,0,1,2,1,1,1,2,2,2>>),
 
602
    ?line check(fun() ->
 
603
                        << <<X:8>> || 
 
604
                            <<65,X:4>> <= <<65,7:4,65,3:4,66,8:4>> >>
 
605
                end,
 
606
                "<< <<X:8>> || 
 
607
                            <<65,X:4>> <= <<65,7:4,65,3:4,66,8:4>> >>.",
 
608
                <<7,3>>),
 
609
    ?line check(fun() -> <<34:18/big>> end,
 
610
                "<<34:18/big>>.",
 
611
                <<0,8,2:2>>),
 
612
    ?line check(fun() -> <<34:18/big-unit:2>> end,
 
613
                "<<34:18/big-unit:2>>.",
 
614
                <<0,0,0,2,2:4>>),
 
615
    ?line check(fun() -> <<34:18/little>> end,
 
616
                "<<34:18/little>>.",
 
617
                <<34,0,0:2>>),
 
618
    ?line case eval_string("<<34:18/native>>.") of
 
619
              <<0,8,2:2>> -> ok;
 
620
              <<34,0,0:2>> -> ok
 
621
          end,
 
622
    ?line check(fun() -> <<34:18/big-signed>> end,
 
623
                "<<34:18/big-signed>>.",
 
624
                <<0,8,2:2>>),
 
625
    ?line check(fun() -> <<34:18/little-signed>> end,
 
626
                "<<34:18/little-signed>>.",
 
627
                <<34,0,0:2>>),
 
628
    ?line case eval_string("<<34:18/native-signed>>.") of
 
629
              <<0,8,2:2>> -> ok;
 
630
              <<34,0,0:2>> -> ok
 
631
          end,
 
632
    ?line check(fun() -> <<34:18/big-unsigned>> end,
 
633
                "<<34:18/big-unsigned>>.",
 
634
                <<0,8,2:2>>),
 
635
    ?line check(fun() -> <<34:18/little-unsigned>> end,
 
636
                "<<34:18/little-unsigned>>.",
 
637
                <<34,0,0:2>>),
 
638
    ?line case eval_string("<<34:18/native-unsigned>>.") of
 
639
              <<0,8,2:2>> -> ok;
 
640
              <<34,0,0:2>> -> ok
 
641
          end,
 
642
    ?line check(fun() -> <<3.14:32/float-big>> end,
 
643
                "<<3.14:32/float-big>>.",
 
644
                <<64,72,245,195>>),
 
645
    ?line check(fun() -> <<3.14:32/float-little>> end,
 
646
                "<<3.14:32/float-little>>.",
 
647
                <<195,245,72,64>>),
 
648
    ?line case eval_string("<<3.14:32/float-native>>.") of
 
649
              <<64,72,245,195>> -> ok;
 
650
              <<195,245,72,64>> -> ok
 
651
          end,
 
652
    ?line error_check("<<(<<17,3:2>>)/binary>>.", badarg),
 
653
    ?line check(fun() -> <<(<<17,3:2>>)/bitstring>> end,
 
654
                "<<(<<17,3:2>>)/bitstring>>.",
 
655
                <<17,3:2>>),
 
656
    ?line check(fun() -> <<(<<17,3:2>>):10/bitstring>> end,
 
657
                "<<(<<17,3:2>>):10/bitstring>>.",
 
658
                <<17,3:2>>),
 
659
    ?line check(fun() -> <<<<344:17>>/binary-unit:17>> end,
 
660
                "<<<<344:17>>/binary-unit:17>>.",
 
661
                <<344:17>>),
 
662
 
 
663
    ?line check(fun() -> <<X:18/big>> = <<34:18/big>>, X end,
 
664
                "begin <<X:18/big>> = <<34:18/big>>, X end.",
 
665
                34),
 
666
    ?line check(fun() -> <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end,
 
667
                "begin <<X:18/big-unit:2>> = <<34:18/big-unit:2>>, X end.",
 
668
                34),
 
669
    ?line check(fun() -> <<X:18/little>> = <<34:18/little>>, X end,
 
670
                "begin <<X:18/little>> = <<34:18/little>>, X end.",
 
671
                34),
 
672
    ?line check(fun() -> <<X:18/native>> = <<34:18/native>>, X end,
 
673
                "begin <<X:18/native>> = <<34:18/native>>, X end.",
 
674
                34),
 
675
    ?line check(fun() -> <<X:18/big-signed>> = <<34:18/big-signed>>, X end,
 
676
                "begin <<X:18/big-signed>> = <<34:18/big-signed>>, X end.",
 
677
                34),
 
678
    ?line check(fun() -> <<X:18/little-signed>> = <<34:18/little-signed>>, 
 
679
                         X end,
 
680
                "begin <<X:18/little-signed>> = <<34:18/little-signed>>, 
 
681
                       X end.",
 
682
                34),
 
683
    ?line check(fun() -> <<X:18/native-signed>> = <<34:18/native-signed>>, 
 
684
                         X end,
 
685
                "begin <<X:18/native-signed>> = <<34:18/native-signed>>, 
 
686
                       X end.",
 
687
                34),
 
688
    ?line check(fun() -> <<X:18/big-unsigned>> = <<34:18/big-unsigned>>, 
 
689
                         X end,
 
690
                "begin <<X:18/big-unsigned>> = <<34:18/big-unsigned>>, 
 
691
                       X end.",
 
692
                34),
 
693
    ?line check(fun() -> 
 
694
                        <<X:18/little-unsigned>> = <<34:18/little-unsigned>>, 
 
695
                        X end,
 
696
                "begin <<X:18/little-unsigned>> = <<34:18/little-unsigned>>, 
 
697
                       X end.",
 
698
                34),
 
699
    ?line check(fun() -> 
 
700
                        <<X:18/native-unsigned>> = <<34:18/native-unsigned>>, 
 
701
                        X end,
 
702
                "begin <<X:18/native-unsigned>> = <<34:18/native-unsigned>>, 
 
703
                       X end.",
 
704
                34),
 
705
    ?line check(fun() -> <<X:32/float-big>> = <<2.0:32/float-big>>, X end,
 
706
                "begin <<X:32/float-big>> = <<2.0:32/float-big>>, 
 
707
                        X end.",
 
708
                2.0),
 
709
    ?line check(fun() -> <<X:32/float-little>> = <<2.0:32/float-little>>, 
 
710
                         X end,
 
711
                "begin <<X:32/float-little>> = <<2.0:32/float-little>>, 
 
712
                        X end.",
 
713
                2.0),
 
714
    ?line check(fun() -> <<X:32/float-native>> = <<2.0:32/float-native>>, 
 
715
                         X end,
 
716
                "begin <<X:32/float-native>> = <<2.0:32/float-native>>, 
 
717
                        X end.",
 
718
                2.0),
 
719
 
 
720
    ?line check(
 
721
            fun() -> 
 
722
                    [X || <<"hej",X:8>> <= <<"hej",8,"san",9,"hej",17,"hej">>]
 
723
            end,
 
724
            "[X || <<\"hej\",X:8>> <= 
 
725
                        <<\"hej\",8,\"san\",9,\"hej\",17,\"hej\">>].",
 
726
            [8,17]),
 
727
    ?line check(
 
728
            fun() ->
 
729
                    L = 8, << <<B:32>> || <<L:L,B:L>> <= <<16:8, 7:16>> >>
 
730
            end,
 
731
            "begin L = 8, << <<B:32>> || <<L:L,B:L>> <= <<16:8, 7:16>> >> 
 
732
             end.",
 
733
            <<0,0,0,7>>),
 
734
    %% Test the Value part of a binary segment. 
 
735
    %% "Old" bugs have been fixed (partial_eval is called on Value).
 
736
    ?line check(fun() -> [ 3 || <<17/float>> <= <<17.0/float>>] end,
 
737
                "[ 3 || <<17/float>> <= <<17.0/float>>].",
 
738
                [3]),
 
739
    ?line check(fun() -> [ 3 || <<17/float>> <- [<<17.0/float>>]] end,
 
740
                "[ 3 || <<17/float>> <- [<<17.0/float>>]].",
 
741
                [3]),
 
742
    ?line check(fun() -> [ X || <<17/float,X:3>> <= <<17.0/float,2:3>>] end,
 
743
                "[ X || <<17/float,X:3>> <= <<17.0/float,2:3>>].",
 
744
                [2]),
 
745
    ?line check(fun() -> 
 
746
                 [ foo || <<(1 bsl 1023)/float>> <= <<(1 bsl 1023)/float>>]
 
747
                end,
 
748
                "[ foo || <<(1 bsl 1023)/float>> <= <<(1 bsl 1023)/float>>].",
 
749
                [foo]),
 
750
    ?line check(fun() -> 
 
751
                 [ foo || <<(1 bsl 1023)/float>> <- [<<(1 bsl 1023)/float>>]]
 
752
                end,
 
753
               "[ foo || <<(1 bsl 1023)/float>> <- [<<(1 bsl 1023)/float>>]].",
 
754
                [foo]),
 
755
    ?line error_check("[ foo || <<(1 bsl 1024)/float>> <- 
 
756
                            [<<(1 bsl 1024)/float>>]].",
 
757
                      badarg),
 
758
    ?line check(fun() -> 
 
759
                 [ foo || <<(1 bsl 1024)/float>> <- [<<(1 bsl 1023)/float>>]]
 
760
                end,
 
761
                "[ foo || <<(1 bsl 1024)/float>> <- 
 
762
                            [<<(1 bsl 1023)/float>>]].",
 
763
                []),
 
764
    ?line check(fun() -> 
 
765
                 [ foo || <<(1 bsl 1024)/float>> <= <<(1 bsl 1023)/float>>]
 
766
                end,
 
767
                "[ foo || <<(1 bsl 1024)/float>> <= 
 
768
                            <<(1 bsl 1023)/float>>].",
 
769
                []),
 
770
    ?line check(fun() ->
 
771
                        L = 8, 
 
772
                        [{L,B} || <<L:L,B:L/float>> <= <<32:8,7:32/float>>]
 
773
                end,
 
774
                "begin L = 8, 
 
775
                       [{L,B} || <<L:L,B:L/float>> <= <<32:8,7:32/float>>]
 
776
                 end.",
 
777
                [{32,7.0}]),
 
778
    ?line check(fun() ->
 
779
                        L = 8, 
 
780
                        [{L,B} || <<L:L,B:L/float>> <- [<<32:8,7:32/float>>]]
 
781
                end,
 
782
                "begin L = 8, 
 
783
                       [{L,B} || <<L:L,B:L/float>> <- [<<32:8,7:32/float>>]]
 
784
                 end.",
 
785
                [{32,7.0}]),
 
786
    ?line check(fun() ->
 
787
                        [foo || <<"s">> <= <<"st">>]
 
788
                end,
 
789
                "[foo || <<\"s\">> <= <<\"st\">>].",
 
790
                [foo]),
 
791
    ?line check(fun() -> <<_:32>> = <<17:32>> end,
 
792
                "<<_:32>> = <<17:32>>.",
 
793
                <<17:32>>),
 
794
    ?line check(fun() -> [foo || <<_:32>> <= <<17:32,20:32>>] end,
 
795
                "[foo || <<_:32>> <= <<17:32,20:32>>].",
 
796
                [foo,foo]),
 
797
 
 
798
    ?line check(fun() -> << <<X:32>> || X <- [1,2,3], X > 1 >> end,
 
799
                "<< <<X:32>> || X <- [1,2,3], X > 1 >>.",
 
800
                <<0,0,0,2,0,0,0,3>>),
 
801
    ?line error_check("[X || <<X>> <= [a,b]].",{bad_generator,[a,b]}),
 
802
    ok.
 
803
 
 
804
otp_6787(doc) ->
 
805
    ["OTP-6787. bitlevel binaries."];
 
806
otp_6787(suite) ->
 
807
    [];
 
808
otp_6787(Config) when is_list(Config) ->
 
809
    ?line check(
 
810
            fun() -> <<16:(1024*1024)>> = <<16:(1024*1024)>> end,
 
811
            "<<16:(1024*1024)>> = <<16:(1024*1024)>>.",
 
812
            <<16:1048576>>),
 
813
    ok.
 
814
 
 
815
otp_6977(doc) ->
 
816
    ["OTP-6977. ++ bug."];
 
817
otp_6977(suite) ->
 
818
    [];
 
819
otp_6977(Config) when is_list(Config) ->
 
820
    ?line check(
 
821
            fun() -> (fun([$X] ++ _) -> ok end)("X") end,
 
822
            "(fun([$X] ++ _) -> ok end)(\"X\").",
 
823
            ok),
 
824
    ok.
 
825
 
 
826
otp_7550(doc) ->
 
827
    ["OTP-7550. Support for UTF-8, UTF-16, UTF-32."];
 
828
otp_7550(Config) when is_list(Config) ->
 
829
 
 
830
    %% UTF-8.
 
831
    ?line check(
 
832
            fun() -> <<65>> = <<65/utf8>> end,
 
833
            "<<65>> = <<65/utf8>>.",
 
834
            <<65>>),
 
835
    ?line check(
 
836
            fun() -> <<350/utf8>> = <<197,158>> end,
 
837
            "<<350/utf8>> = <<197,158>>.",
 
838
            <<197,158>>),
 
839
    ?line check(
 
840
            fun() -> <<$b,$j,$\303,$\266,$r,$n>> = <<"bj\366rn"/utf8>> end,
 
841
            "<<$b,$j,$\303,$\266,$r,$n>> = <<\"bj\366rn\"/utf8>>.",
 
842
            <<$b,$j,$\303,$\266,$r,$n>>),
 
843
 
 
844
    %% UTF-16.
 
845
    ?line check(
 
846
            fun() -> <<0,65>> = <<65/utf16>> end,
 
847
            "<<0,65>> = <<65/utf16>>.",
 
848
            <<0,65>>),
 
849
    ?line check(
 
850
            fun() -> <<16#D8,16#08,16#DF,16#45>> = <<16#12345/utf16>> end,
 
851
            "<<16#D8,16#08,16#DF,16#45>> = <<16#12345/utf16>>.",
 
852
            <<16#D8,16#08,16#DF,16#45>>),
 
853
    ?line check(
 
854
            fun() -> <<16#08,16#D8,16#45,16#DF>> = <<16#12345/little-utf16>> end,
 
855
            "<<16#08,16#D8,16#45,16#DF>> = <<16#12345/little-utf16>>.",
 
856
            <<16#08,16#D8,16#45,16#DF>>),
 
857
 
 
858
    ?line check(
 
859
            fun() -> <<350/utf16>> = <<1,94>> end,
 
860
            "<<350/utf16>> = <<1,94>>.",
 
861
            <<1,94>>),
 
862
    ?line check(
 
863
            fun() -> <<350/little-utf16>> = <<94,1>> end,
 
864
            "<<350/little-utf16>> = <<94,1>>.",
 
865
            <<94,1>>),
 
866
    ?line check(
 
867
            fun() -> <<16#12345/utf16>> = <<16#D8,16#08,16#DF,16#45>> end,
 
868
            "<<16#12345/utf16>> = <<16#D8,16#08,16#DF,16#45>>.",
 
869
            <<16#D8,16#08,16#DF,16#45>>),
 
870
    ?line check(
 
871
            fun() -> <<16#12345/little-utf16>> = <<16#08,16#D8,16#45,16#DF>> end,
 
872
            "<<16#12345/little-utf16>> = <<16#08,16#D8,16#45,16#DF>>.",
 
873
            <<16#08,16#D8,16#45,16#DF>>),
 
874
 
 
875
    %% UTF-32.
 
876
    ?line check(
 
877
            fun() -> <<16#12345/utf32>> = <<16#0,16#01,16#23,16#45>> end,
 
878
            "<<16#12345/utf32>> = <<16#0,16#01,16#23,16#45>>.",
 
879
            <<16#0,16#01,16#23,16#45>>),
 
880
    ?line check(
 
881
            fun() -> <<16#0,16#01,16#23,16#45>> = <<16#12345/utf32>> end,
 
882
            "<<16#0,16#01,16#23,16#45>> = <<16#12345/utf32>>.",
 
883
            <<16#0,16#01,16#23,16#45>>),
 
884
    ?line check(
 
885
            fun() -> <<16#12345/little-utf32>> = <<16#45,16#23,16#01,16#00>> end,
 
886
            "<<16#12345/little-utf32>> = <<16#45,16#23,16#01,16#00>>.",
 
887
            <<16#45,16#23,16#01,16#00>>),
 
888
    ?line check(
 
889
            fun() -> <<16#12345/little-utf32>> end,
 
890
            "<<16#12345/little-utf32>>.",
 
891
            <<16#45,16#23,16#01,16#00>>),
 
892
 
 
893
    %% Mixed.
 
894
    ?line check(
 
895
            fun() -> <<16#41,16#12345/utf32,16#0391:16,16#2E:8>> end,
 
896
            "<<16#41,16#12345/utf32,16#0391:16,16#2E:8>>.",
 
897
            <<16#41,16#00,16#01,16#23,16#45,16#03,16#91,16#2E>>),
 
898
    ok.
 
899
 
 
900
 
 
901
otp_8133(doc) ->
 
902
    ["OTP-8133. Bit comprehension bug."];
 
903
otp_8133(suite) ->
 
904
    [];
 
905
otp_8133(Config) when is_list(Config) ->
 
906
    ?line check(
 
907
            fun() ->
 
908
                  E = fun(N) -> 
 
909
                              if 
 
910
                                  is_integer(N) -> <<N/integer>>; 
 
911
                                  true -> throw(foo) 
 
912
                              end 
 
913
                      end,
 
914
                  try << << (E(V))/binary >> || V <- [1,2,3,a] >> 
 
915
                  catch foo -> ok
 
916
                  end
 
917
            end,
 
918
            "begin
 
919
                 E = fun(N) -> 
 
920
                            if is_integer(N) -> <<N/integer>>; 
 
921
                               true -> throw(foo) 
 
922
                            end 
 
923
                     end,
 
924
                 try << << (E(V))/binary >> || V <- [1,2,3,a] >> 
 
925
                 catch foo -> ok
 
926
                 end
 
927
             end.",
 
928
            ok),
 
929
    ?line check(
 
930
            fun() ->
 
931
                  E = fun(N) -> 
 
932
                              if 
 
933
                                  is_integer(N) -> <<N/integer>>; 
 
934
                                  true -> erlang:error(foo) 
 
935
                              end 
 
936
                      end,
 
937
                  try << << (E(V))/binary >> || V <- [1,2,3,a] >> 
 
938
                  catch error:foo -> ok
 
939
                  end
 
940
            end,
 
941
            "begin
 
942
                 E = fun(N) -> 
 
943
                            if is_integer(N) -> <<N/integer>>; 
 
944
                               true -> erlang:error(foo) 
 
945
                            end 
 
946
                     end,
 
947
                 try << << (E(V))/binary >> || V <- [1,2,3,a] >> 
 
948
                 catch error:foo -> ok
 
949
                 end
 
950
             end.",
 
951
            ok),
 
952
    ok.
 
953
 
 
954
funs(doc) ->
 
955
    ["Simple cases, just to cover some code."];
 
956
funs(suite) ->
 
957
    [];
 
958
funs(Config) when is_list(Config) ->
 
959
    do_funs(none, none),
 
960
    do_funs(lfh(), none),
 
961
    do_funs(lfh(), efh()),
 
962
 
 
963
    ?line error_check("nix:foo().", {access_not_allowed,nix}, lfh(), efh()),
 
964
    ?line error_check("bar().", undef, none, none),
 
965
 
 
966
    ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
 
967
                         F1(F1, 1000) end,
 
968
                "begin F1 = fun(F,N) -> count_down(F, N) end,"
 
969
                "F1(F1,1000) end.",
 
970
                0, ['F1'], lfh(), none),
 
971
 
 
972
    ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
 
973
                         F1(F1, 1000) end,
 
974
                "begin F1 = fun(F,N) -> count_down(F, N) end,"
 
975
                "F1(F1,1000) end.",
 
976
                0, ['F1'], lfh_value(), none),
 
977
 
 
978
    ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
 
979
                         F1(F1, 1000) end,
 
980
                "begin F1 = fun(F,N) -> count_down(F, N) end,"
 
981
                "F1(F1,1000) end.",
 
982
                0, ['F1'], lfh_value_extra(), none),
 
983
 
 
984
    ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
 
985
                         F1(F1, 1000) end,
 
986
                "begin F1 = fun(F,N) -> count_down(F, N) end,"
 
987
                "F1(F1,1000) end.",
 
988
                0, ['F1'], {?MODULE,local_func_value}, none),
 
989
    %% This is not documented, and only for backward compatibility (good!).
 
990
    B0 = erl_eval:new_bindings(),
 
991
    ?line check(fun() -> is_function(?MODULE:count_down_fun()) end,
 
992
                "begin is_function(count_down_fun()) end.",
 
993
                true, [], {?MODULE,local_func,[B0]},none),
 
994
 
 
995
    EF = fun({timer,sleep}, As) when length(As) == 1 -> exit({got_it,sleep});
 
996
            ({M,F}, As) -> apply(M, F, As)
 
997
         end,
 
998
    EFH = {value, EF},
 
999
    ?line error_check("apply(timer, sleep, [1]).", got_it, none, EFH),
 
1000
    ?line error_check("begin F = fun(T) -> timer:sleep(T) end,F(1) end.",
 
1001
                      got_it, none, EFH),
 
1002
    ?line error_check("fun c/1.", undef),
 
1003
    ?line error_check("fun a:b/0().", undef),
 
1004
 
 
1005
    MaxArgs = 20,
 
1006
    ?line [true] = 
 
1007
        lists:usort([run_many_args(SAs) || SAs <- many_args(MaxArgs)]),
 
1008
    ?line {'EXIT',{{argument_limit,_},_}} = 
 
1009
        (catch run_many_args(many_args1(MaxArgs+1))),
 
1010
    ok.
 
1011
 
 
1012
run_many_args({S, As}) ->
 
1013
    apply(eval_string(S), As) =:= As.
 
1014
 
 
1015
many_args(N) ->
 
1016
    [many_args1(I) || I <- lists:seq(1, N)].
 
1017
 
 
1018
many_args1(N) ->
 
1019
    F = fun(L, P) -> 
 
1020
                tl(lists:flatten([","++P++integer_to_list(E) || E <- L]))
 
1021
        end,
 
1022
    L = lists:seq(1, N),
 
1023
    T = F(L, "V"),
 
1024
    S = lists:flatten(io_lib:format("fun(~s) -> [~s] end.", [T, T])),
 
1025
    {S, L}.
 
1026
 
 
1027
do_funs(LFH, EFH) ->
 
1028
    %% LFH is not really used by these examples...
 
1029
 
 
1030
    %% These tests do not prove that tail recursive functions really
 
1031
    %% work (that the process does not grow); one should also run them
 
1032
    %% manually with 1000 replaced by 1000000.
 
1033
 
 
1034
    M = atom_to_list(?MODULE),
 
1035
    ?line check(fun() -> F1 = fun(F,N) -> ?MODULE:count_down(F, N) end,
 
1036
                         F1(F1, 1000) end,
 
1037
                concat(["begin F1 = fun(F,N) -> ", M, 
 
1038
                        ":count_down(F, N) end, F1(F1,1000) end."]),
 
1039
                0, ['F1'], LFH, EFH),
 
1040
    ?line check(fun() -> F1 = fun(F,N) -> apply(?MODULE,count_down,[F,N]) 
 
1041
                              end, F1(F1, 1000) end,
 
1042
                concat(["begin F1 = fun(F,N) -> apply(", M, 
 
1043
                        ",count_down,[F, N]) end, F1(F1,1000) end."]),
 
1044
                0, ['F1'], LFH, EFH),
 
1045
    ?line check(fun() -> F1 = fun(F,N) -> {?MODULE,count_down}(F,N)
 
1046
                              end, F1(F1, 1000) end,
 
1047
                concat(["begin F1 = fun(F,N) -> {", M, 
 
1048
                        ",count_down}(F, N) end, F1(F1,1000) end."]),
 
1049
                0, ['F1'], LFH, EFH),
 
1050
    ?line check(fun() -> F = fun(F,N) when N > 0 -> apply(F,[F,N-1]); 
 
1051
                                (_F,0) -> ok end, 
 
1052
                         F(F, 1000)
 
1053
                end,
 
1054
                "begin F = fun(F,N) when N > 0 -> apply(F,[F,N-1]);"
 
1055
                             "(_F,0) -> ok end,"
 
1056
                       "F(F, 1000) end.",
 
1057
                ok, ['F'], LFH, EFH),
 
1058
    ?line check(fun() -> F = fun(F,N) when N > 0 -> 
 
1059
                                     apply(erlang,apply,[F,[F,N-1]]);
 
1060
                                (_F,0) -> ok end, 
 
1061
                         F(F, 1000)
 
1062
                end,
 
1063
                "begin F = fun(F,N) when N > 0 ->"
 
1064
                                   "apply(erlang,apply,[F,[F,N-1]]);"
 
1065
                             "(_F,0) -> ok end,"
 
1066
                       "F(F, 1000) end.",
 
1067
                ok, ['F'], LFH, EFH),
 
1068
    ?line check(fun() -> F = count_down_fun(), 
 
1069
                         SF = fun(SF, F1, N) -> F(SF, F1, N) end,
 
1070
                         SF(SF, F, 1000) end,
 
1071
                concat(["begin F = ", M, ":count_down_fun(),"
 
1072
                        "SF = fun(SF, F1, N) -> F(SF, F1, N) end,"
 
1073
                        "SF(SF, F, 1000) end."]),
 
1074
                ok, ['F','SF'], LFH, EFH),
 
1075
 
 
1076
 
 
1077
    ?line check(fun() -> F = fun(X) -> A = 1+X, {X,A} end, 
 
1078
                         true = {2,3} == F(2) end,
 
1079
                "begin F = fun(X) -> A = 1+X, {X,A} end, 
 
1080
                       true = {2,3} == F(2) end.", true, ['F'], LFH, EFH),
 
1081
    ?line check(fun() -> F = fun(X) -> {erlang,'+'}(X,2) end, 
 
1082
                         true = 3 == F(1) end,
 
1083
                "begin F = fun(X) -> {erlang,'+'}(X,2) end," 
 
1084
                "      true = 3 == F(1) end.", true, ['F'],
 
1085
               LFH, EFH),
 
1086
    ?line check(fun() -> F = fun(X) -> byte_size(X) end,
 
1087
                         ?MODULE:do_apply(F,<<"hej">>) end, 
 
1088
                concat(["begin F = fun(X) -> size(X) end,",
 
1089
                        M,":do_apply(F,<<\"hej\">>) end."]),
 
1090
                3, ['F'], LFH, EFH),
 
1091
 
 
1092
    ?line check(fun() -> F1 = fun(X, Z) -> {X,Z} end,
 
1093
                         Z = 5,
 
1094
                         F2 = fun(X, Y) -> F1(Z,{X,Y}) end,
 
1095
                         F3 = fun(X, Y) -> {a,F1(Z,{X,Y})} end,
 
1096
                         {5,{x,y}} = F2(x,y), 
 
1097
                         {a,{5,{y,x}}} = F3(y,x), 
 
1098
                         {5,{5,y}} = F2(Z,y), 
 
1099
                         true = {5,{x,5}} == F2(x,Z) end,
 
1100
                "begin F1 = fun(X, Z) -> {X,Z} end,
 
1101
                       Z = 5,
 
1102
                       F2 = fun(X, Y) -> F1(Z,{X,Y}) end,
 
1103
                       F3 = fun(X, Y) -> {a,F1(Z,{X,Y})} end,
 
1104
                       {5,{x,y}} = F2(x,y), 
 
1105
                       {a,{5,{y,x}}} = F3(y,x), 
 
1106
                       {5,{5,y}} = F2(Z,y), 
 
1107
                       true = {5,{x,5}} == F2(x,Z) end.",
 
1108
                true, ['F1','Z','F2','F3'], LFH, EFH),
 
1109
    ?line check(fun() -> F = fun(X) -> byte_size(X) end,
 
1110
                         F2 = fun(Y) -> F(Y) end,
 
1111
                         ?MODULE:do_apply(F2,<<"hej">>) end, 
 
1112
                concat(["begin F = fun(X) -> size(X) end,",
 
1113
                        "F2 = fun(Y) -> F(Y) end,",
 
1114
                        M,":do_apply(F2,<<\"hej\">>) end."]),
 
1115
                3, ['F','F2'], LFH, EFH),
 
1116
    ?line check(fun() -> Z = 5, F = fun(X) -> {Z,X} end,
 
1117
                         F2 = fun(Z) -> F(Z) end, F2(3) end,
 
1118
                "begin Z = 5, F = fun(X) -> {Z,X} end,
 
1119
                       F2 = fun(Z) -> F(Z) end, F2(3) end.",
 
1120
                {5,3},['F','F2','Z'], LFH, EFH),
 
1121
    ?line check(fun() -> F = fun(Z) -> Z end,
 
1122
                         F2 = fun(X) -> F(X), Z = {X,X}, Z end,
 
1123
                         {1,1} = F2(1), Z = 7, Z end,
 
1124
                "begin F = fun(Z) -> Z end,
 
1125
                       F2 = fun(X) -> F(X), Z = {X,X}, Z end,
 
1126
                       {1,1} = F2(1), Z = 7, Z end.", 7, ['F','F2','Z'], 
 
1127
                LFH, EFH),
 
1128
    ?line check(fun() -> F = fun(F, N) -> [?MODULE:count_down(F,N) || X <-[1]]
 
1129
                             end, F(F,2) end,
 
1130
                concat(["begin F = fun(F, N) -> [", M, 
 
1131
                       ":count_down(F,N) || X <-[1]] end, F(F,2) end."]),
 
1132
                [[[0]]], ['F'], LFH, EFH),
 
1133
 
 
1134
    %% Tests for a bug found by the Dialyzer - used to crash.
 
1135
    ?line check(fun() -> Pmod = erl_eval_helper:new(42), Pmod:add(5) end,
 
1136
                "begin Pmod = erl_eval_helper:new(42), Pmod:add(5) end.",
 
1137
                47,
 
1138
                ['Pmod'], LFH, EFH),
 
1139
    ?line check(fun() -> Pmod = erl_eval_helper:new(42), B = Pmod:add(7), B end,
 
1140
                "begin Pmod = erl_eval_helper:new(42), B = Pmod:add(7), B end.",
 
1141
                49,
 
1142
                ['B','Pmod'], LFH, EFH),
 
1143
 
 
1144
    ok.
 
1145
 
 
1146
count_down(F, N) when N > 0 ->
 
1147
    F(F, N-1);
 
1148
count_down(_F, N) ->
 
1149
    N.
 
1150
 
 
1151
count_down_fun() ->
 
1152
    fun(SF,F,N) when N > 0 -> SF(SF,F,N-1);
 
1153
       (_SF,_F,_N) -> ok
 
1154
    end.
 
1155
 
 
1156
do_apply(F, V) ->
 
1157
    F(V).
 
1158
 
 
1159
lfh() ->
 
1160
    {eval, fun(F, As, Bs) -> local_func(F, As, Bs) end}.
 
1161
 
 
1162
local_func(F, As0, Bs0) when is_atom(F) ->
 
1163
    {As,Bs} = erl_eval:expr_list(As0, Bs0, {eval,lfh()}),
 
1164
    case erlang:function_exported(?MODULE, F, length(As)) of
 
1165
        true ->
 
1166
            {value,apply(?MODULE, F, As),Bs};
 
1167
        false ->
 
1168
            {value,apply(shell_default, F, As),Bs}
 
1169
    end.
 
1170
 
 
1171
lfh_value_extra() ->
 
1172
    %% Not documented.
 
1173
    {value, fun(F, As) -> local_func_value(F, As) end, []}.
 
1174
 
 
1175
lfh_value() ->
 
1176
    {value, fun(F, As) -> local_func_value(F, As) end}.
 
1177
 
 
1178
local_func_value(F, As) when is_atom(F) ->
 
1179
    case erlang:function_exported(?MODULE, F, length(As)) of
 
1180
        true ->
 
1181
            apply(?MODULE, F, As);
 
1182
        false ->
 
1183
            apply(shell_default, F, As)
 
1184
    end.
 
1185
 
 
1186
efh() ->
 
1187
    {value, fun(F, As) -> external_func(F, As) end}.
 
1188
 
 
1189
external_func({M,_}, _As) when M == nix ->
 
1190
    exit({{access_not_allowed,M},[mfa]});
 
1191
external_func(F, As) when is_function(F) ->
 
1192
    apply(F, As);
 
1193
external_func({M,F}, As) ->
 
1194
    apply(M, F, As).
 
1195
 
 
1196
 
 
1197
 
 
1198
try_catch(doc) ->
 
1199
    ["Test try-of-catch-after-end statement"];
 
1200
try_catch(suite) -> 
 
1201
    [];
 
1202
try_catch(Config) when is_list(Config) ->
 
1203
    %% Match in of with catch
 
1204
    ?line check(fun() -> try 1 of 1 -> 2 catch _:_ -> 3 end end,
 
1205
                "try 1 of 1 -> 2 catch _:_ -> 3 end.", 2),
 
1206
    ?line check(fun() -> try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
 
1207
                "try 1 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end.", 2),
 
1208
    ?line check(fun() -> try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end end,
 
1209
                "try 3 of 1 -> 2; 3 -> 4 catch _:_ -> 5 end.", 4),
 
1210
    %% Just after
 
1211
    ?line check(fun () -> X = try 1 after put(try_catch, 2) end,
 
1212
                          {X,get(try_catch)} end,
 
1213
                "begin X = try 1 after put(try_catch, 2) end, "
 
1214
                "{X,get(try_catch)} end.", {1,2}),
 
1215
    %% Match in of with after
 
1216
    ?line check(fun() -> X = try 1 of 1 -> 2 after put(try_catch, 3) end,
 
1217
                         {X,get(try_catch)} end,
 
1218
                "begin X = try 1 of 1 -> 2 after put(try_catch, 3) end, "
 
1219
                "{X,get(try_catch)} end.", {2,3}),
 
1220
    ?line check(fun() -> X = try 1 of 1 -> 2; 3 -> 4 
 
1221
                             after put(try_catch, 5) end,
 
1222
                         {X,get(try_catch)} end,
 
1223
                "begin X = try 1 of 1 -> 2; 3 -> 4 "
 
1224
                "          after put(try_catch, 5) end, "
 
1225
                "      {X,get(try_catch)} end.", {2,5}),
 
1226
    ?line check(fun() -> X = try 3 of 1 -> 2; 3 -> 4 
 
1227
                             after put(try_catch, 5) end,
 
1228
                         {X,get(try_catch)} end,
 
1229
                "begin X = try 3 of 1 -> 2; 3 -> 4 "
 
1230
                "          after put(try_catch, 5) end, "
 
1231
                "      {X,get(try_catch)} end.", {4,5}),
 
1232
    %% Nomatch in of
 
1233
    ?line error_check("try 1 of 2 -> 3 catch _:_ -> 4 end.",
 
1234
                      {try_clause,1}),
 
1235
    %% Nomatch in of with after
 
1236
    ?line check(fun () -> {'EXIT',{{try_clause,1},_}} = 
 
1237
                              begin catch try 1 of 2 -> 3
 
1238
                                          after put(try_catch, 4) end end,
 
1239
                          get(try_catch) end,
 
1240
                "begin {'EXIT',{{try_clause,1},_}} = "
 
1241
                "          begin catch try 1 of 2 -> 3 "
 
1242
                "                      after put(try_catch, 4) end end, "
 
1243
                "      get(try_catch) end. ", 4),
 
1244
    %% Exception in try
 
1245
    ?line check(fun () -> try 1=2 catch error:{badmatch,2} -> 3 end end,
 
1246
                "try 1=2 catch error:{badmatch,2} -> 3 end.", 3),
 
1247
    ?line check(fun () -> try 1=2 of 3 -> 4 
 
1248
                          catch error:{badmatch,2} -> 5 end end,
 
1249
                "try 1=2 of 3 -> 4 "
 
1250
                "catch error:{badmatch,2} -> 5 end.", 5),
 
1251
    %% Exception in try with after
 
1252
    ?line check(fun () -> X = try 1=2 
 
1253
                              catch error:{badmatch,2} -> 3
 
1254
                              after put(try_catch, 4) end,
 
1255
                          {X,get(try_catch)} end,
 
1256
                "begin X = try 1=2 "
 
1257
                "          catch error:{badmatch,2} -> 3 "
 
1258
                "          after put(try_catch, 4) end, "
 
1259
                "      {X,get(try_catch)} end. ", {3,4}),
 
1260
    ?line check(fun () -> X = try 1=2 of 3 -> 4
 
1261
                              catch error:{badmatch,2} -> 5
 
1262
                              after put(try_catch, 6) end,
 
1263
                          {X,get(try_catch)} end,
 
1264
                "begin X = try 1=2 of 3 -> 4"
 
1265
                "          catch error:{badmatch,2} -> 5 "
 
1266
                "          after put(try_catch, 6) end, "
 
1267
                "      {X,get(try_catch)} end. ", {5,6}),
 
1268
    %% Uncaught exception
 
1269
    ?line error_check("try 1=2 catch error:undefined -> 3 end. ",
 
1270
                      {badmatch,2}),
 
1271
    ?line error_check("try 1=2 of 3 -> 4 catch error:undefined -> 5 end. ",
 
1272
                      {badmatch,2}),
 
1273
    %% Uncaught exception with after
 
1274
    ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
 
1275
                              begin catch try 1=2 
 
1276
                                          after put(try_catch, 3) end end,
 
1277
                          get(try_catch) end,
 
1278
                "begin {'EXIT',{{badmatch,2},_}} = "
 
1279
                "          begin catch try 1=2 "
 
1280
                "                      after put(try_catch, 3) end end, "
 
1281
                "      get(try_catch) end. ", 3),
 
1282
    ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
 
1283
                              begin catch try 1=2 of 3 -> 4
 
1284
                                          after put(try_catch, 5) end end,
 
1285
                          get(try_catch) end,
 
1286
                "begin {'EXIT',{{badmatch,2},_}} = "
 
1287
                "          begin catch try 1=2 of 3 -> 4"
 
1288
                "                      after put(try_catch, 5) end end, "
 
1289
                "      get(try_catch) end. ", 5),
 
1290
    ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
 
1291
                              begin catch try 1=2 catch error:undefined -> 3
 
1292
                                          after put(try_catch, 4) end end,
 
1293
                          get(try_catch) end,
 
1294
                "begin {'EXIT',{{badmatch,2},_}} = "
 
1295
                "          begin catch try 1=2 catch error:undefined -> 3 "
 
1296
                "                      after put(try_catch, 4) end end, "
 
1297
                "      get(try_catch) end. ", 4),
 
1298
    ?line check(fun () -> {'EXIT',{{badmatch,2},_}} =
 
1299
                              begin catch try 1=2 of 3 -> 4
 
1300
                                          catch error:undefined -> 5
 
1301
                                          after put(try_catch, 6) end end,
 
1302
                          get(try_catch) end,
 
1303
                "begin {'EXIT',{{badmatch,2},_}} = "
 
1304
                "          begin catch try 1=2 of 3 -> 4 "
 
1305
                "                      catch error:undefined -> 5 "
 
1306
                "                      after put(try_catch, 6) end end, "
 
1307
                "      get(try_catch) end. ", 6),
 
1308
    ok.
 
1309
 
 
1310
 
 
1311
eval_expr_5(doc) ->
 
1312
    ["(OTP-7933)"];
 
1313
eval_expr_5(suite) ->
 
1314
    [];
 
1315
eval_expr_5(Config) when is_list(Config) ->
 
1316
    ?line {ok,Tokens ,_} =
 
1317
        erl_scan:string("if a+4 == 4 -> yes; true -> no end. "),
 
1318
    ?line {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
 
1319
    ?line {value, no, []} = erl_eval:expr(Expr, [], none, none, none),
 
1320
    ?line no = erl_eval:expr(Expr, [], none, none, value),
 
1321
    try
 
1322
        erl_eval:expr(Expr, [], none, none, 4711),
 
1323
        ?line function_clause = should_never_reach_here
 
1324
    catch
 
1325
        error:function_clause ->
 
1326
            ok
 
1327
    end.
 
1328
 
 
1329
%% Check the string in different contexts: as is; in fun; from compiled code.
 
1330
check(F, String, Result) ->
 
1331
    check1(F, String, Result),
 
1332
    FunString = concat(["fun() -> ", no_final_dot(String), " end(). "]),
 
1333
    check1(F, FunString, Result),
 
1334
    CompileString = concat(["hd(lists:map(fun(_) -> ", no_final_dot(String), 
 
1335
                            " end, [foo])). "]),
 
1336
    check1(F, CompileString, Result).
 
1337
 
 
1338
check1(F, String, Result) ->
 
1339
    Result = F(),
 
1340
    case catch parse_and_run(String) of
 
1341
        {value, Result, _} ->
 
1342
            ok;
 
1343
        Other ->
 
1344
            test_server:fail({eval, Other, Result})
 
1345
    end.
 
1346
 
 
1347
check(F, String, Result, BoundVars, LFH, EFH) ->
 
1348
    Result = F(),
 
1349
    case catch parse_and_run(String, LFH, EFH) of
 
1350
        {value, Result, Bs} ->
 
1351
            %% We just assume that Bs is an orddict...
 
1352
            Keys = orddict:fetch_keys(Bs),
 
1353
            case sort(BoundVars) == Keys of
 
1354
                true -> 
 
1355
                    ok;
 
1356
                false -> 
 
1357
                    test_server:fail({check, BoundVars, Keys})
 
1358
            end,
 
1359
            ok;
 
1360
        Other ->
 
1361
            test_server:fail({check, Other, Result})
 
1362
    end.
 
1363
 
 
1364
error_check(String, Result) ->
 
1365
    case catch parse_and_run(String) of
 
1366
        {'EXIT', {Result,_}} ->
 
1367
            ok;
 
1368
        Other ->
 
1369
            test_server:fail({eval, Other, Result})
 
1370
    end.
 
1371
 
 
1372
error_check(String, Result, LFH, EFH) ->
 
1373
    case catch parse_and_run(String, LFH, EFH) of
 
1374
        {'EXIT', {Result,_}} ->
 
1375
            ok;
 
1376
        Other ->
 
1377
            test_server:fail({eval, Other, Result})
 
1378
    end.
 
1379
 
 
1380
eval_string(String) ->
 
1381
    {value, Result, _} = parse_and_run(String),
 
1382
    Result.
 
1383
 
 
1384
parse_and_run(String) ->
 
1385
    {ok,Tokens,_} = erl_scan:string(String),
 
1386
    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
 
1387
    erl_eval:expr(Expr, []).
 
1388
 
 
1389
parse_and_run(String, LFH, EFH) ->
 
1390
    {ok,Tokens,_} = erl_scan:string(String),
 
1391
    {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
 
1392
    erl_eval:expr(Expr, [], LFH, EFH).
 
1393
 
 
1394
no_final_dot(S) ->
 
1395
    case lists:reverse(S) of
 
1396
        " ." ++ R -> lists:reverse(R);
 
1397
        "." ++ R -> lists:reverse(R);
 
1398
        _ -> S
 
1399
    end.