~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - 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.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
 
19
19
-module(escript_SUITE).
20
20
-export([
21
 
         all/1,
 
21
        all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
22
         init_per_group/2,end_per_group/2,
22
23
         init_per_testcase/2,
23
 
         fin_per_testcase/2,
 
24
         end_per_testcase/2,
24
25
         basic/1,
25
 
         errors/1, 
 
26
         errors/1,
26
27
         strange_name/1,
27
28
         emulator_flags/1,
28
29
         module_script/1,
29
30
         beam_script/1,
30
31
         archive_script/1,
31
 
         epp/1
 
32
         epp/1,
 
33
         create_and_extract/1,
 
34
         foldl/1,
 
35
         overflow/1,
 
36
         verify_sections/3
32
37
        ]).
33
38
 
34
 
-include("test_server.hrl").
35
 
 
36
 
all(suite) ->
37
 
    [
38
 
     basic,
39
 
     errors,
40
 
     strange_name,
41
 
     emulator_flags,
42
 
     module_script,
43
 
     beam_script,
44
 
     archive_script,
45
 
     epp
46
 
    ].
 
39
-include_lib("test_server/include/test_server.hrl").
 
40
-include_lib("kernel/include/file.hrl").
 
41
 
 
42
suite() -> [{ct_hooks,[ts_install_cth]}].
 
43
 
 
44
all() -> 
 
45
    [basic, errors, strange_name, emulator_flags,
 
46
     module_script, beam_script, archive_script, epp,
 
47
     create_and_extract, foldl, overflow].
 
48
 
 
49
groups() -> 
 
50
    [].
 
51
 
 
52
init_per_suite(Config) ->
 
53
    Config.
 
54
 
 
55
end_per_suite(_Config) ->
 
56
    ok.
 
57
 
 
58
init_per_group(_GroupName, Config) ->
 
59
    Config.
 
60
 
 
61
end_per_group(_GroupName, Config) ->
 
62
    Config.
47
63
 
48
64
init_per_testcase(_Case, Config) ->
49
65
    ?line Dog = ?t:timetrap(?t:minutes(1)),
50
66
    [{watchdog,Dog}|Config].
51
67
 
52
 
fin_per_testcase(_Case, Config) ->
 
68
end_per_testcase(_Case, Config) ->
53
69
    Dog = ?config(watchdog, Config),
54
70
    test_server:timetrap_cancel(Dog),
55
71
    ok.
68
84
    ?line run(Dir, "factorial_warning 20",
69
85
              [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\n"
70
86
                         "factorial 20 = 2432902008176640000\nExitCode:0">>]),
71
 
    ?line run(Dir, "-s", "factorial_warning",
72
 
              [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
73
 
    ?line run(Dir, "-s -i", "factorial_warning",
74
 
              [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
75
 
    ?line run(Dir, "-c -s", "factorial_warning",
 
87
    ?line run_with_opts(Dir, "-s", "factorial_warning",
 
88
              [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
 
89
    ?line run_with_opts(Dir, "-s -i", "factorial_warning",
 
90
              [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
 
91
    ?line run_with_opts(Dir, "-c -s", "factorial_warning",
76
92
              [data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
77
93
    ?line run(Dir, "filesize "++filename:join(?config(data_dir, Config),"filesize"),
78
94
              [data_dir,<<"filesize:11: Warning: function id/1 is unused\n324\nExitCode:0">>]),
100
116
              [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
101
117
               data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
102
118
               <<"escript: There were compilation errors.\nExitCode:127">>]),
103
 
    ?line run(Dir, "-s", "lint_error",
 
119
    ?line run_with_opts(Dir, "-s", "lint_error",
104
120
              [data_dir,<<"lint_error:6: function main/1 already defined\n">>,
105
121
               data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
106
122
               <<"escript: There were compilation errors.\nExitCode:127">>]),
140
156
    OrigFile = filename:join([Data,"emulator_flags"]),
141
157
    {ok, OrigBin} = file:read_file(OrigFile),
142
158
    ?line [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
143
 
    ?line {ok, OrigFI} = file:read_file_info(OrigFile),    
 
159
    ?line {ok, OrigFI} = file:read_file_info(OrigFile),
144
160
 
145
161
    %% Write source file
146
162
    Priv = ?config(priv_dir, Config),
147
163
    Dir = filename:absname(Priv), % Get rid of trailing slash.
148
164
    Base = "module_script",
149
165
    ErlFile = filename:join([Priv, Base ++ ".erl"]),
150
 
    ErlCode = ["-module(", Base, ").\n",
 
166
    ErlCode = ["\n-module(", Base, ").\n",
151
167
               "-export([main/1]).\n\n",
152
168
               string:join(Source, "\n"),
153
169
               "\n"],
154
170
    ?line ok = file:write_file(ErlFile, ErlCode),
155
 
    
 
171
 
156
172
    %%%%%%%
157
173
    %% Create and run scripts without emulator flags
158
174
 
159
175
    %% With shebang
160
176
    NoArgsBase = Base ++ "_no_args_with_shebang",
161
177
    NoArgsFile = filename:join([Priv, NoArgsBase]),
162
 
    ?line ok = file:write_file(NoArgsFile, 
 
178
    ?line ok = file:write_file(NoArgsFile,
163
179
                               [Shebang, "\n",
164
180
                                ErlCode]),
165
181
    ?line ok = file:write_file_info(NoArgsFile, OrigFI),
166
 
    
167
 
    ?line run(Dir, NoArgsBase ++  " -arg1 arg2 arg3",
 
182
 
 
183
    ?line run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
168
184
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
169
185
                "nostick:[]\n"
170
186
                "mnesia:[]\n"
172
188
                "unknown:[]\n"
173
189
                "ExitCode:0">>]),
174
190
 
175
 
    ?line run(Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
 
191
    ?line run_with_opts(Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
176
192
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
177
193
                "nostick:[]\n"
178
194
                "mnesia:[]\n"
183
199
    %% Without shebang
184
200
    NoArgsBase2 = Base ++ "_no_args_without_shebang",
185
201
    NoArgsFile2 = filename:join([Priv, NoArgsBase2]),
186
 
    ?line ok = file:write_file(NoArgsFile2, 
 
202
    ?line ok = file:write_file(NoArgsFile2,
187
203
                               ["Something else than shebang!!!", "\n",
188
204
                                ErlCode]),
189
205
    ?line ok = file:write_file_info(NoArgsFile2, OrigFI),
190
 
   
191
 
    ?line run(Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
 
206
 
 
207
    ?line run_with_opts(Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
192
208
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
193
209
                "nostick:[]\n"
194
210
                "mnesia:[]\n"
195
211
                "ERL_FLAGS=false\n"
196
212
                "unknown:[]\n"
197
213
                "ExitCode:0">>]),
198
 
    
 
214
 
199
215
    %% Plain module without header
200
216
    NoArgsBase3 = Base ++ "_no_args_without_header",
201
217
    NoArgsFile3 = filename:join([Priv, NoArgsBase3]),
202
218
    ?line ok = file:write_file(NoArgsFile3, [ErlCode]),
203
219
    ?line ok = file:write_file_info(NoArgsFile3, OrigFI),
204
 
    
205
 
    ?line run(Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
 
220
 
 
221
    ?line run_with_opts(Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
206
222
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
207
223
                "nostick:[]\n"
208
224
                "mnesia:[]\n"
209
225
                "ERL_FLAGS=false\n"
210
226
                "unknown:[]\n"
211
227
                "ExitCode:0">>]),
212
 
    
 
228
 
213
229
    %%%%%%%
214
230
    %% Create and run scripts with emulator flags
215
231
 
217
233
    ArgsBase = Base ++ "_args_with_shebang",
218
234
    ArgsFile = filename:join([Priv, ArgsBase]),
219
235
    ?line ok = file:write_file(ArgsFile,
220
 
                               [Shebang, "\n", 
 
236
                               [Shebang, "\n",
221
237
                                Mode, "\n",
222
238
                                Flags, "\n",
223
239
                                ErlCode]),
224
 
    ?line ok = file:write_file_info(ArgsFile, OrigFI),    
225
 
    
 
240
    ?line ok = file:write_file_info(ArgsFile, OrigFI),
 
241
 
226
242
    ?line run(Dir, ArgsBase ++  " -arg1 arg2 arg3",
227
243
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
228
244
                "nostick:[{nostick,[]}]\n"
242
258
    OrigFile = filename:join([Data,"emulator_flags"]),
243
259
    {ok, OrigBin} = file:read_file(OrigFile),
244
260
    ?line [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
245
 
    ?line {ok, OrigFI} = file:read_file_info(OrigFile),    
 
261
    ?line {ok, OrigFI} = file:read_file_info(OrigFile),
246
262
 
247
263
    %% Write source file
248
264
    Priv = ?config(priv_dir, Config),
249
265
    Dir = filename:absname(Priv), % Get rid of trailing slash.
250
266
    Base = "beam_script",
251
267
    ErlFile = filename:join([Priv, Base ++ ".erl"]),
252
 
    ?line ok = file:write_file(ErlFile, 
253
 
                               ["-module(", Base, ").\n",
 
268
    ?line ok = file:write_file(ErlFile,
 
269
                               ["\n-module(", Base, ").\n",
254
270
                                "-export([main/1]).\n\n",
255
271
                                string:join(Source, "\n"),
256
272
                                "\n"]),
257
273
 
258
274
    %% Compile the code
259
275
    ?line {ok, _Mod, BeamCode} = compile:file(ErlFile, [binary]),
260
 
    
 
276
 
261
277
    %%%%%%%
262
278
    %% Create and run scripts without emulator flags
263
279
 
264
280
    %% With shebang
265
281
    NoArgsBase = Base ++ "_no_args_with_shebang",
266
282
    NoArgsFile = filename:join([Priv, NoArgsBase]),
267
 
    ?line ok = file:write_file(NoArgsFile, 
 
283
    ?line ok = file:write_file(NoArgsFile,
268
284
                               [Shebang, "\n",
269
285
                                BeamCode]),
270
 
    ?line ok = file:write_file_info(NoArgsFile, OrigFI),    
 
286
    ?line ok = file:write_file_info(NoArgsFile, OrigFI),
271
287
 
272
288
    ?line run(Dir, NoArgsBase ++  " -arg1 arg2 arg3",
273
289
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
277
293
                "unknown:[]\n"
278
294
                "ExitCode:0">>]),
279
295
 
280
 
    ?line run(Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
 
296
    ?line run_with_opts(Dir, "", NoArgsBase ++  " -arg1 arg2 arg3",
281
297
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
282
298
                "nostick:[]\n"
283
299
                "mnesia:[]\n"
288
304
    %% Without shebang
289
305
    NoArgsBase2 = Base ++ "_no_args_without_shebang",
290
306
    NoArgsFile2 = filename:join([Priv, NoArgsBase2]),
291
 
    ?line ok = file:write_file(NoArgsFile2, 
 
307
    ?line ok = file:write_file(NoArgsFile2,
292
308
                               ["Something else than shebang!!!", "\n",
293
309
                                BeamCode]),
294
 
    ?line ok = file:write_file_info(NoArgsFile2, OrigFI),    
 
310
    ?line ok = file:write_file_info(NoArgsFile2, OrigFI),
295
311
 
296
 
    ?line run(Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
 
312
    ?line run_with_opts(Dir, "", NoArgsBase2 ++  " -arg1 arg2 arg3",
297
313
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
298
314
                "nostick:[]\n"
299
315
                "mnesia:[]\n"
305
321
    NoArgsBase3 = Base ++ "_no_args_without_header",
306
322
    NoArgsFile3 = filename:join([Priv, NoArgsBase3]),
307
323
    ?line ok = file:write_file(NoArgsFile3, [BeamCode]),
308
 
    ?line ok = file:write_file_info(NoArgsFile3, OrigFI),    
 
324
    ?line ok = file:write_file_info(NoArgsFile3, OrigFI),
309
325
 
310
 
    ?line run(Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
 
326
    ?line run_with_opts(Dir, "", NoArgsBase3 ++  " -arg1 arg2 arg3",
311
327
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
312
328
                "nostick:[]\n"
313
329
                "mnesia:[]\n"
322
338
    ArgsBase = Base ++ "_args",
323
339
    ArgsFile = filename:join([Priv, ArgsBase]),
324
340
    ?line ok = file:write_file(ArgsFile,
325
 
                               [Shebang, "\n", 
 
341
                               [Shebang, "\n",
326
342
                                Mode, "\n",
327
343
                                Flags, "\n",
328
344
                                BeamCode]),
329
 
    ?line ok = file:write_file_info(ArgsFile, OrigFI),    
330
 
    
 
345
    ?line ok = file:write_file_info(ArgsFile, OrigFI),
 
346
 
331
347
    ?line run(Dir, ArgsBase ++  " -arg1 arg2 arg3",
332
348
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
333
349
                "nostick:[{nostick,[]}]\n"
356
372
    ?line ok = compile_app(TopDir, "archive_script_dict"),
357
373
    ?line ok = compile_app(TopDir, "archive_script_dummy"),
358
374
    ?line {ok, MainFiles} = file:list_dir(TopDir),
359
 
    ?line ok = compile_files(MainFiles, TopDir, TopDir),    
360
 
    
 
375
    ?line ok = compile_files(MainFiles, TopDir, TopDir),
 
376
 
361
377
    %% Create the archive
362
378
    {ok, TopFiles} = file:list_dir(TopDir),
363
379
    ?line {ok, {_, ArchiveBin}} = zip:create(Archive, TopFiles,
364
380
                                             [memory, {compress, []}, {cwd, TopDir}]),
365
 
    
 
381
 
366
382
    %% Read the source script
367
383
    OrigFile = filename:join([DataDir, "emulator_flags"]),
368
384
    {ok, OrigBin} = file:read_file(OrigFile),
371
387
    Flags = "%%! -archive_script_dict foo bar"
372
388
        " -archive_script_dict foo"
373
389
        " -archive_script_dummy bar",
374
 
    ?line {ok, OrigFI} = file:read_file_info(OrigFile),    
375
 
    
 
390
    ?line {ok, OrigFI} = file:read_file_info(OrigFile),
 
391
 
376
392
    %%%%%%%
377
393
    %% Create and run scripts without emulator flags
378
 
    MainBase = "archive_script_main", 
379
 
    MainScript = filename:join([PrivDir, MainBase]), 
 
394
    MainBase = "archive_script_main",
 
395
    MainScript = filename:join([PrivDir, MainBase]),
380
396
 
381
397
    %% With shebang
382
 
    ?line ok = file:write_file(MainScript, 
 
398
    ?line ok = file:write_file(MainScript,
383
399
                               [Shebang, "\n",
384
400
                                Flags, "\n",
385
401
                                ArchiveBin]),
386
 
    ?line ok = file:write_file_info(MainScript, OrigFI),    
387
 
   
 
402
    ?line ok = file:write_file_info(MainScript, OrigFI),
 
403
 
388
404
    ?line run(PrivDir, MainBase ++  " -arg1 arg2 arg3",
389
 
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n" 
390
 
                "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
391
 
                "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
392
 
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
393
 
                "ExitCode:0">>]),
394
 
 
395
 
    ?line run(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
396
 
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n" 
397
 
                "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
398
 
                "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
399
 
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
400
 
                "ExitCode:0">>]),
401
 
    
 
405
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 
406
                "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
 
407
                "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
 
408
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
 
409
                "ExitCode:0">>]),
 
410
 
 
411
    ?line run_with_opts(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
 
412
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
 
413
                "dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
 
414
                "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
 
415
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
 
416
                "ExitCode:0">>]),
 
417
 
402
418
    ?line ok = file:rename(MainScript, MainScript ++ "_with_shebang"),
403
419
 
404
420
    %% Without shebang (no flags)
405
 
    ?line ok = file:write_file(MainScript, 
 
421
    ?line ok = file:write_file(MainScript,
406
422
                               ["Something else than shebang!!!", "\n",
407
423
                                ArchiveBin]),
408
 
    ?line ok = file:write_file_info(MainScript, OrigFI),    
409
 
   
410
 
    ?line run(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
411
 
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n" 
 
424
    ?line ok = file:write_file_info(MainScript, OrigFI),
 
425
 
 
426
    ?line run_with_opts(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
 
427
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
412
428
                "dict:[]\n"
413
429
                "dummy:[]\n"
414
430
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
415
431
                "ExitCode:0">>]),
416
432
    ?line ok = file:rename(MainScript, MainScript ++ "_without_shebang"),
417
 
    
 
433
 
418
434
    %% Plain archive without header (no flags)
419
 
    
 
435
 
420
436
    ?line ok = file:write_file(MainScript, [ArchiveBin]),
421
 
    ?line ok = file:write_file_info(MainScript, OrigFI),    
422
 
   
423
 
    ?line run(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
424
 
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n" 
 
437
    ?line ok = file:write_file_info(MainScript, OrigFI),
 
438
 
 
439
    ?line run_with_opts(PrivDir, "", MainBase ++  " -arg1 arg2 arg3",
 
440
              [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
425
441
                "dict:[]\n"
426
442
                "dummy:[]\n"
427
443
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
428
444
                "ExitCode:0">>]),
429
445
    ?line ok = file:rename(MainScript, MainScript ++ "_without_header"),
430
 
    
 
446
 
431
447
    %%%%%%%
432
448
    %% Create and run scripts with emulator flags
433
449
    AltBase = "archive_script_alternate_main",
434
450
    AltScript = filename:join([PrivDir, AltBase]),
435
 
    ?line ok = file:write_file(AltScript, 
 
451
    ?line ok = file:write_file(AltScript,
436
452
                               [Shebang, "\n",
437
453
                                Mode, "\n",
438
454
                                Flags, " -escript main archive_script_main2\n",
439
455
                                ArchiveBin]),
440
 
    ?line ok = file:write_file_info(AltScript, OrigFI),    
 
456
    ?line ok = file:write_file_info(AltScript, OrigFI),
441
457
 
442
458
    ?line run(PrivDir, AltBase ++  " -arg1 arg2 arg3",
443
459
              [<<"main2:[\"-arg1\",\"arg2\",\"arg3\"]\n"
445
461
                "dummy:[{archive_script_dummy,[\"bar\"]}]\n"
446
462
                "priv:{ok,<<\"Some private data...\\n\">>}\n"
447
463
                "ExitCode:0">>]),
448
 
    
 
464
 
449
465
    ok.
450
466
 
451
467
compile_app(TopDir, AppName) ->
482
498
 
483
499
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
484
500
 
 
501
create_and_extract(Config) when is_list(Config) ->
 
502
    {NewFile, FileInfo,
 
503
     EmuArg, Source,
 
504
     _ErlBase, ErlCode,
 
505
     _BeamBase, BeamCode,
 
506
     ArchiveBin} =
 
507
        prepare_creation("create_and_extract", Config),
 
508
 
 
509
    Bodies =
 
510
        [[{source, ErlCode}],
 
511
         [{beam, BeamCode}],
 
512
         [{archive, ArchiveBin}]],
 
513
 
 
514
    %% Verify all combinations of scripts with shebangs
 
515
    [verify_sections(NewFile, FileInfo, S ++ C ++ E ++ B) ||
 
516
        S <- [[{shebang, default}],
 
517
              [{shebang, "/usr/bin/env     escript"}]],
 
518
        C <- [[],
 
519
              [{comment, undefined}],
 
520
              [{comment, default}],
 
521
              [{comment, "This is a nonsense comment"}]],
 
522
        E <- [[],
 
523
              [{emu_args, undefined}],
 
524
              [{emu_args, EmuArg}]],
 
525
        B <- [[{source, Source}] | Bodies]],
 
526
 
 
527
    %% Verify all combinations of scripts without shebangs
 
528
    [verify_sections(NewFile, FileInfo, S ++ C ++ E ++ B) ||
 
529
        S <- [[], [{shebang, undefined}]],
 
530
        C <- [[], [{comment, undefined}]],
 
531
        E <- [[], [{emu_args, undefined}]],
 
532
        B <- Bodies],
 
533
 
 
534
    %% Verify the compile_source option
 
535
    file:delete(NewFile),
 
536
    ?line ok = escript:create(NewFile, [{source, Source}]),
 
537
    ?line {ok, [_, _, _, {source, Source}]} = escript:extract(NewFile, []),
 
538
    ?line {ok, [_, _, _, {source, BeamCode2}]} =
 
539
        escript:extract(NewFile, [compile_source]),
 
540
    verify_sections(NewFile, FileInfo,
 
541
                    [{shebang, default},
 
542
                     {comment, default},
 
543
                     {beam, BeamCode2}]),
 
544
 
 
545
    file:delete(NewFile),
 
546
    ok.
 
547
 
 
548
prepare_creation(Base, Config) ->
 
549
    %% Read the source
 
550
    PrivDir = ?config(priv_dir, Config),
 
551
    DataDir = ?config(data_dir, Config),
 
552
    OrigFile = filename:join([DataDir,"emulator_flags"]),
 
553
    ?line {ok, FileInfo} = file:read_file_info(OrigFile),
 
554
    NewFile = filename:join([PrivDir, Base]),
 
555
    ?line {ok, [{shebang, default},
 
556
                {comment, _},
 
557
                {emu_args, EmuArg},
 
558
                {source, Source}]} =
 
559
        escript:extract(OrigFile, []),
 
560
 
 
561
    %% Compile the code
 
562
    ErlFile = NewFile ++ ".erl",
 
563
    ErlCode = list_to_binary(["\n-module(", Base, ").\n",
 
564
                              "-export([main/1]).\n\n",
 
565
                              Source, "\n\n"]),
 
566
    ?line ok = file:write_file(ErlFile, ErlCode),
 
567
 
 
568
    %% Compile the code
 
569
    ?line {ok, _Mod, BeamCode} =
 
570
        compile:file(ErlFile, [binary, debug_info]),
 
571
 
 
572
    %% Create an archive
 
573
    ?line {ok, {_, ArchiveBin}} =
 
574
        zip:create("dummy_archive_name",
 
575
                   [{Base ++ ".erl", ErlCode},
 
576
                    {Base ++ ".beam", BeamCode}],
 
577
                   [{compress, []}, memory]),
 
578
    {NewFile, FileInfo,
 
579
     EmuArg, Source,
 
580
     Base ++ ".erl", ErlCode,
 
581
     Base ++ ".beam", BeamCode,
 
582
     ArchiveBin}.
 
583
 
 
584
verify_sections(File, FileInfo, Sections) ->
 
585
    io:format("~p:verify_sections(\n\t~p,\n\t~p,\n\t~p).\n",
 
586
              [?MODULE, File, FileInfo, Sections]),
 
587
 
 
588
    %% Create
 
589
    file:delete(File),
 
590
    ?line ok = escript:create(File, Sections),
 
591
    ?line ok = file:write_file_info(File, FileInfo),
 
592
 
 
593
    %% Run
 
594
    Dir = filename:absname(filename:dirname(File)),
 
595
    Base = filename:basename(File),
 
596
 
 
597
    HasArg = fun(Tag) ->
 
598
                     case lists:keysearch(Tag, 1, Sections) of
 
599
                         false -> false;
 
600
                         {value, {_, undefined}} -> false;
 
601
                         {value, _} -> true
 
602
                     end
 
603
             end,
 
604
    ExpectedMain = <<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n">>,
 
605
    ExpectedOutput =
 
606
        case HasArg(emu_args) of
 
607
            true ->
 
608
                <<"nostick:[{nostick,[]}]\n"
 
609
                  "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
 
610
                  "ERL_FLAGS=false\n"
 
611
                  "unknown:[]\n"
 
612
                  "ExitCode:0">>;
 
613
            false ->
 
614
                <<"nostick:[]\nmnesia:[]\nERL_FLAGS=false\nunknown:[]\nExitCode:0">>
 
615
        end,
 
616
 
 
617
    InputArgs = Base ++ " -arg1 arg2 arg3",
 
618
    Expected = <<ExpectedMain/binary, ExpectedOutput/binary>>,
 
619
    case HasArg(shebang) of
 
620
        true ->
 
621
            ?line run(Dir, InputArgs, [Expected]);
 
622
        false ->
 
623
            ?line run_with_opts(Dir, [], InputArgs, [Expected])
 
624
    end,
 
625
 
 
626
    %% Verify
 
627
    ?line {ok, Bin} = escript:create(binary, Sections),
 
628
    ?line {ok, Read} = file:read_file(File),
 
629
    ?line Bin = Read, % Assert
 
630
 
 
631
    Normalized = normalize_sections(Sections),
 
632
    ?line {ok, Extracted} = escript:extract(File, []),
 
633
    io:format("Normalized; ~p\n", [Normalized]),
 
634
    io:format("Extracted ; ~p\n", [Extracted]),
 
635
    ?line Normalized = Extracted, % Assert
 
636
    ok.
 
637
 
 
638
normalize_sections(Sections) ->
 
639
    AtomToTuple =
 
640
        fun(Val) ->
 
641
                if
 
642
                    is_atom(Val) -> {Val, default};
 
643
                    true -> Val
 
644
                end
 
645
        end,
 
646
    case lists:map(AtomToTuple, [{K, V} || {K, V} <- Sections, V =/= undefined]) of
 
647
            [{shebang, Shebang} | Rest] ->
 
648
                [{shebang, Shebang} |
 
649
                 case Rest of
 
650
                     [{comment, Comment} | Rest2] ->
 
651
                         [{comment, Comment} |
 
652
                          case Rest2 of
 
653
                              [{emu_args, EmuArgs}, Body] ->
 
654
                                  [{emu_args, EmuArgs}, Body];
 
655
                              [Body] ->
 
656
                                  [{emu_args, undefined}, Body]
 
657
                          end
 
658
                         ];
 
659
                     [{emu_args, EmuArgs}, Body] ->
 
660
                         [{comment, undefined}, {emu_args, EmuArgs}, Body];
 
661
                     [Body] ->
 
662
                         [{comment, undefined}, {emu_args, undefined}, Body]
 
663
                 end
 
664
                ];
 
665
            [Body] ->
 
666
                [{shebang, undefined}, {comment, undefined}, {emu_args, undefined}, Body]
 
667
        end.
 
668
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
669
 
 
670
foldl(Config) when is_list(Config) ->
 
671
    {NewFile, _FileInfo,
 
672
     _EmuArg, _Source,
 
673
     ErlBase, ErlCode,
 
674
     BeamBase, _BeamCode,
 
675
     ArchiveBin} =
 
676
        prepare_creation("foldl", Config),
 
677
 
 
678
    Collect = fun(Name, GetInfo, GetBin, Acc) ->
 
679
                      [{Name, GetInfo(), GetBin()} | Acc]
 
680
              end,
 
681
 
 
682
    %% Get line numbers and the file attribute right
 
683
    SourceFile = NewFile ++ ".erl",
 
684
    <<_:1/binary, ErlCode2/binary>> = ErlCode,
 
685
    ?line ok = file:write_file(SourceFile, ErlCode2),
 
686
    ?line {ok, _Mod, BeamCode} =
 
687
        compile:file(SourceFile, [binary, debug_info]),
 
688
 
 
689
    %% Verify source script
 
690
    ?line ok = escript:create(SourceFile, [{source, ErlCode}]),
 
691
    ?line {ok, [{".", _, BeamCode2}]}
 
692
        = escript_foldl(Collect, [], SourceFile),
 
693
 
 
694
    ?line {ok, Abstr} = beam_lib:chunks(BeamCode, [abstract_code]),
 
695
    ?line {ok, Abstr2} = beam_lib:chunks(BeamCode2, [abstract_code]),
 
696
    %% io:format("abstr1=~p\n", [Abstr]),
 
697
    %% io:format("abstr2=~p\n", [Abstr2]),
 
698
    ?line Abstr = Abstr2, % Assert
 
699
 
 
700
    %% Verify beam script
 
701
    ?line ok = escript:create(NewFile, [{beam, BeamCode}]),
 
702
    ?line {ok, [{".", _, BeamCode}]}
 
703
        = escript_foldl(Collect, [], NewFile),
 
704
 
 
705
    %% Verify archive scripts
 
706
    ?line ok = escript:create(NewFile, [{archive, ArchiveBin}]),
 
707
    ?line {ok, [{BeamBase, #file_info{}, _},
 
708
                {ErlBase, #file_info{}, _}]}
 
709
        = escript_foldl(Collect, [], NewFile),
 
710
 
 
711
    ArchiveFiles = [{ErlBase, ErlCode}, {BeamBase, BeamCode}],
 
712
    ?line ok = escript:create(NewFile, [{archive, ArchiveFiles, []}]),
 
713
    ?line {ok, [{BeamBase, _, _},
 
714
              {ErlBase, _, _}]}
 
715
        = escript_foldl(Collect, [], NewFile),
 
716
 
 
717
    ok.
 
718
 
 
719
escript_foldl(Fun, Acc, File) ->
 
720
    code:ensure_loaded(zip),
 
721
    case erlang:function_exported(zip, foldl, 3) of
 
722
        true ->
 
723
            emulate_escript_foldl(Fun, Acc, File);
 
724
        false ->
 
725
            escript:foldl(Fun, Acc, File)
 
726
    end.
 
727
 
 
728
emulate_escript_foldl(Fun, Acc, File) ->
 
729
    case escript:extract(File, [compile_source]) of
 
730
        {ok, [_Shebang, _Comment, _EmuArgs, Body]} ->
 
731
            case Body of
 
732
                {source, BeamCode} ->
 
733
                    GetInfo = fun() -> file:read_file_info(File) end,
 
734
                    GetBin = fun() -> BeamCode end,
 
735
                    {ok, Fun(".", GetInfo, GetBin, Acc)};
 
736
                {beam, BeamCode} ->
 
737
                    GetInfo = fun() -> file:read_file_info(File) end,
 
738
                    GetBin = fun() -> BeamCode end,
 
739
                    {ok, Fun(".", GetInfo, GetBin, Acc)};
 
740
                {archive, ArchiveBin} ->
 
741
                    zip:foldl(Fun, Acc, {File, ArchiveBin})
 
742
            end;
 
743
        {error, Reason} ->
 
744
            {error, Reason}
 
745
    end.
 
746
 
 
747
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
748
 
 
749
overflow(Config) when is_list(Config) ->
 
750
    Data = ?config(data_dir, Config),
 
751
    Dir = filename:absname(Data),               %Get rid of trailing slash.
 
752
    ?line run(Dir, "arg_overflow",
 
753
              [<<"ExitCode:0">>]),
 
754
    ?line run(Dir, "linebuf_overflow",
 
755
              [<<"ExitCode:0">>]),
 
756
    ok.
 
757
 
 
758
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
759
 
485
760
run(Dir, Cmd0, Expected0) ->
486
761
    Expected = iolist_to_binary(expected_output(Expected0, Dir)),
487
762
    Cmd = case os:type() of
490
765
          end,
491
766
    do_run(Dir, Cmd, Expected).
492
767
 
493
 
run(Dir, Opts, Cmd0, Expected) ->
 
768
run_with_opts(Dir, Opts, Cmd0, Expected) ->
494
769
    Cmd = case os:type() of
495
770
              {win32,_} -> "escript " ++ Opts ++ " " ++ filename:nativename(Dir) ++ "\\" ++ Cmd0;
496
771
              _ -> "escript " ++ Opts ++ " " ++ Dir ++ "/" ++ Cmd0
533
808
    [filename:nativename(Data)++Slash|expected_output(T, Data)];
534
809
expected_output([H|T], Data) ->
535
810
    [H|expected_output(T, Data)];
536
 
expected_output([], _) -> 
 
811
expected_output([], _) ->
537
812
    [];
538
 
expected_output(Bin, _) when is_binary(Bin) -> 
 
813
expected_output(Bin, _) when is_binary(Bin) ->
539
814
    Bin.
540
815