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

« back to all changes in this revision

Viewing changes to lib/reltool/test/reltool_server_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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2011. 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(reltool_server_SUITE).
 
20
 
 
21
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, 
 
22
         init_per_suite/1, end_per_suite/1, 
 
23
         init_per_testcase/2, end_per_testcase/2]).
 
24
 
 
25
-compile(export_all).
 
26
 
 
27
-include("reltool_test_lib.hrl").
 
28
 
 
29
-define(NODE_NAME, '__RELTOOL__TEMPORARY_TEST__NODE__').
 
30
-define(WORK_DIR, "reltool_work_dir").
 
31
 
 
32
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
33
%% Initialization functions.
 
34
 
 
35
init_per_suite(Config) ->
 
36
    ?ignore(file:make_dir(?WORK_DIR)),
 
37
    reltool_test_lib:init_per_suite(Config).
 
38
 
 
39
end_per_suite(Config) ->
 
40
    reltool_test_lib:end_per_suite(Config).
 
41
 
 
42
init_per_testcase(Func,Config) ->
 
43
    reltool_test_lib:init_per_testcase(Func,Config).
 
44
end_per_testcase(Func,Config) -> 
 
45
    reltool_test_lib:end_per_testcase(Func,Config).
 
46
 
 
47
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
48
%% SUITE specification
 
49
 
 
50
suite() -> [{ct_hooks,[ts_install_cth]}].
 
51
 
 
52
all() -> 
 
53
    [start_server, set_config, create_release,
 
54
     create_script, create_target, create_embedded,
 
55
     create_standalone, create_old_target].
 
56
 
 
57
groups() -> 
 
58
    [].
 
59
 
 
60
init_per_group(_GroupName, Config) ->
 
61
    Config.
 
62
 
 
63
end_per_group(_GroupName, Config) ->
 
64
    Config.
 
65
 
 
66
 
 
67
%% The test cases
 
68
 
 
69
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
70
%% Start a server process and check that it does not crash
 
71
 
 
72
start_server(TestInfo) when is_atom(TestInfo) -> 
 
73
    reltool_test_lib:tc_info(TestInfo);
 
74
start_server(_Config) ->
 
75
    {ok, Pid} = ?msym({ok, _}, reltool:start_server([])),
 
76
    Libs = lists:sort(erl_libs()),
 
77
    StrippedDefault =
 
78
        case Libs of
 
79
            [] -> {sys, []};
 
80
            _  -> {sys, [{lib_dirs, Libs}]}
 
81
        end,
 
82
    ?m({ok, StrippedDefault}, reltool:get_config(Pid)),
 
83
    ?m(ok, reltool:stop(Pid)),
 
84
    ok.
 
85
 
 
86
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
87
%% Start a server process and check that it does not crash
 
88
 
 
89
set_config(TestInfo) when is_atom(TestInfo) -> 
 
90
    reltool_test_lib:tc_info(TestInfo);
 
91
set_config(_Config) ->
 
92
    Libs = lists:sort(erl_libs()),
 
93
    Default =
 
94
        {sys,
 
95
         [
 
96
          {mod_cond, all},
 
97
          {incl_cond, derived},
 
98
          {root_dir, code:root_dir()},
 
99
          {lib_dirs, Libs}
 
100
         ]},
 
101
    {ok, Pid} = ?msym({ok, _}, reltool:start_server([{config, Default}])),
 
102
    StrippedDefault =
 
103
        case Libs of
 
104
            [] -> {sys, []};
 
105
            _  -> {sys, [{lib_dirs, Libs}]}
 
106
        end,
 
107
    ?m({ok, StrippedDefault}, reltool:get_config(Pid)),
 
108
 
 
109
    ?m(ok, reltool:stop(Pid)),
 
110
    ok.
 
111
 
 
112
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
113
%% Generate releases
 
114
 
 
115
create_release(TestInfo) when is_atom(TestInfo) -> 
 
116
    reltool_test_lib:tc_info(TestInfo);
 
117
create_release(_Config) ->
 
118
    %% Configure the server
 
119
    RelName = "Just testing...",
 
120
    RelVsn = "1.0",
 
121
    Config =
 
122
        {sys,
 
123
         [
 
124
          {lib_dirs, []},
 
125
          {boot_rel, RelName},
 
126
          {rel, RelName, RelVsn, [kernel, stdlib]}
 
127
         ]},
 
128
    %% Generate release 
 
129
    ErtsVsn = erlang:system_info(version),
 
130
    Apps = application:loaded_applications(),
 
131
    {value, {_, _, KernelVsn}} = lists:keysearch(kernel, 1, Apps),
 
132
    {value, {_, _, StdlibVsn}} = lists:keysearch(stdlib, 1, Apps),
 
133
    Rel = {release, {RelName, RelVsn}, 
 
134
           {erts, ErtsVsn}, 
 
135
           [{kernel, KernelVsn}, {stdlib, StdlibVsn}]},
 
136
    ?m({ok, Rel}, reltool:get_rel([{config, Config}], RelName)),
 
137
    ok.
 
138
 
 
139
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
140
%% Generate boot scripts
 
141
 
 
142
create_script(TestInfo) when is_atom(TestInfo) -> 
 
143
    reltool_test_lib:tc_info(TestInfo);
 
144
create_script(_Config) ->
 
145
    %% Configure the server
 
146
    RelName = "Just testing",
 
147
    RelVsn = "1.0",
 
148
    Config =
 
149
        {sys,
 
150
         [
 
151
          {lib_dirs, []},
 
152
          {boot_rel, RelName},
 
153
          {rel, RelName, RelVsn, [stdlib, kernel]}
 
154
         ]},
 
155
    {ok, Pid} = ?msym({ok, _}, reltool:start_server([{config, Config}])),
 
156
 
 
157
    %% Generate release file
 
158
    ErtsVsn = erlang:system_info(version),
 
159
    Apps = application:loaded_applications(),
 
160
    {value, {_, _, KernelVsn}} = lists:keysearch(kernel, 1, Apps),
 
161
    {value, {_, _, StdlibVsn}} = lists:keysearch(stdlib, 1, Apps),
 
162
    Rel = {release, 
 
163
           {RelName, RelVsn}, 
 
164
           {erts, ErtsVsn},
 
165
           [{kernel, KernelVsn}, {stdlib, StdlibVsn}]},
 
166
    ?m({ok, Rel}, reltool:get_rel(Pid, RelName)),
 
167
    ?m(ok, file:write_file(filename:join([?WORK_DIR, RelName ++ ".rel"]),
 
168
                           io_lib:format("~p.\n", [Rel]))),
 
169
 
 
170
    %% Generate script file
 
171
    {ok, Cwd} = file:get_cwd(),
 
172
    ?m(ok, file:set_cwd(?WORK_DIR)),
 
173
    ?m(ok, systools:make_script(RelName, [])),
 
174
    {ok, [OrigScript]} = ?msym({ok, [_]}, file:consult(RelName ++ ".script")),
 
175
    ?m(ok, file:set_cwd(Cwd)),
 
176
    {ok, Script} = ?msym({ok, _}, reltool:get_script(Pid, RelName)),
 
177
    %% OrigScript2 = sort_script(OrigScript),
 
178
    %% Script2 = sort_script(Script),
 
179
    %% ?m(OrigScript2, Script2),
 
180
    
 
181
    ?m(equal, diff_script(OrigScript, Script)),
 
182
    
 
183
    %% Stop server
 
184
    ?m(ok, reltool:stop(Pid)),
 
185
    ok.
 
186
 
 
187
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
188
%% Generate target system
 
189
 
 
190
create_target(TestInfo) when is_atom(TestInfo) -> 
 
191
    reltool_test_lib:tc_info(TestInfo);
 
192
create_target(_Config) ->
 
193
    %% Configure the server
 
194
    RelName1 = "Just testing",
 
195
    RelName2 = "Just testing with SASL",
 
196
    RelVsn = "1.0",
 
197
    Config =
 
198
        {sys,
 
199
         [
 
200
          {root_dir, code:root_dir()},
 
201
          {lib_dirs, []},
 
202
          {boot_rel, RelName2},
 
203
          {rel, RelName1, RelVsn, [stdlib, kernel]},
 
204
          {rel, RelName2, RelVsn, [sasl, stdlib, kernel]},
 
205
          {app, sasl, [{incl_cond, include}]}
 
206
         ]},
 
207
 
 
208
    %% Generate target file
 
209
    TargetDir = filename:join([?WORK_DIR, "target_development"]),
 
210
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
211
    ?m(ok, file:make_dir(TargetDir)),
 
212
    ?log("SPEC: ~p\n", [reltool:get_target_spec([{config, Config}])]),
 
213
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
214
    
 
215
    Erl = filename:join([TargetDir, "bin", "erl"]),
 
216
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)),
 
217
    ?msym(ok, stop_node(Node)),
 
218
    
 
219
    ok.
 
220
 
 
221
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
222
%% Generate embedded target system
 
223
 
 
224
create_embedded(TestInfo) when is_atom(TestInfo) -> 
 
225
    reltool_test_lib:tc_info(TestInfo);
 
226
create_embedded(_Config) ->
 
227
    %% Configure the server
 
228
    RelName1 = "Just testing",
 
229
    RelName2 = "Just testing with SASL",
 
230
    RelVsn = "1.0",
 
231
    Config =
 
232
        {sys,
 
233
         [
 
234
          {lib_dirs, []},
 
235
          {profile, embedded},
 
236
          {boot_rel, RelName2},
 
237
          {rel, RelName1, RelVsn, [stdlib, kernel]},
 
238
          {rel, RelName2, RelVsn, [sasl, stdlib, kernel]},
 
239
          {app, sasl, [{incl_cond, include}]}
 
240
         ]},
 
241
 
 
242
    %% Generate target file
 
243
    TargetDir = filename:join([?WORK_DIR, "target_embedded"]),
 
244
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
245
    ?m(ok, file:make_dir(TargetDir)),
 
246
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
247
 
 
248
    Erl = filename:join([TargetDir, "bin", "erl"]),
 
249
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)),
 
250
    ?msym(ok, stop_node(Node)),
 
251
        
 
252
    ok.
 
253
 
 
254
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
255
%% Generate standalone system
 
256
 
 
257
create_standalone(TestInfo) when is_atom(TestInfo) -> 
 
258
    reltool_test_lib:tc_info(TestInfo);
 
259
create_standalone(_Config) ->
 
260
    %% Configure the server
 
261
    ExDir = code:lib_dir(reltool, examples),
 
262
    EscriptName = "display_args",
 
263
    Escript = filename:join([ExDir, EscriptName]),
 
264
    Config =
 
265
        {sys,
 
266
         [
 
267
          {lib_dirs, []},
 
268
          {escript, Escript, [{incl_cond, include}]},
 
269
          {profile, standalone}
 
270
         ]},
 
271
 
 
272
    %% Generate target file
 
273
    TargetDir = filename:join([?WORK_DIR, "target_standalone"]),
 
274
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
275
    ?m(ok, file:make_dir(TargetDir)),
 
276
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
277
 
 
278
    BinDir = filename:join([TargetDir, "bin"]),
 
279
    Erl = filename:join([BinDir, "erl"]),
 
280
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)), 
 
281
    RootDir = ?ignore(rpc:call(Node, code, root_dir, [])),
 
282
    ?msym(ok, stop_node(Node)),
 
283
    
 
284
    Expected =  iolist_to_binary(["Root dir: ", RootDir, "\n"
 
285
                                  "Script args: [\"-arg1\",\"arg2\",\"arg3\"]\n",
 
286
                                  "Smp: false\n",
 
287
                                  "ExitCode:0"]),
 
288
    io:format("Expected: ~s\n", [Expected]),
 
289
    ?m(Expected, run(BinDir, EscriptName ++ " -arg1 arg2 arg3")),
 
290
    
 
291
    ok.
 
292
 
 
293
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
294
%% Generate old type of target system
 
295
 
 
296
create_old_target(TestInfo) when is_atom(TestInfo) -> 
 
297
    reltool_test_lib:tc_info(TestInfo);
 
298
create_old_target(_Config) ->
 
299
    ?skip("Old style of target", []),
 
300
    
 
301
    %% Configure the server
 
302
    RelName1 = "Just testing",
 
303
    RelName2 = "Just testing with SASL",
 
304
    RelVsn = "1.0",
 
305
    Config =
 
306
        {sys,
 
307
         [
 
308
          {lib_dirs, []},
 
309
          {boot_rel, RelName2},
 
310
          {rel, RelName1, RelVsn, [stdlib, kernel]},
 
311
          {rel, RelName2, RelVsn, [sasl, stdlib, kernel]},
 
312
          {relocatable, false}, % Implies explicit old style installation
 
313
          {app, sasl, [{incl_cond, include}]}
 
314
         ]},
 
315
 
 
316
    %% Generate target file
 
317
    TargetDir = filename:join([?WORK_DIR, "target_old_style"]),
 
318
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
319
    ?m(ok, file:make_dir(TargetDir)),
 
320
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
321
    
 
322
    %% io:format("Will fail on Windows (should patch erl.ini)\n", []),
 
323
    ?m(ok, reltool:install(RelName2, TargetDir)),
 
324
 
 
325
    Erl = filename:join([TargetDir, "bin", "erl"]),
 
326
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)),
 
327
    ?msym(ok, stop_node(Node)),
 
328
    
 
329
    ok.
 
330
 
 
331
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
332
%% Library functions
 
333
 
 
334
erl_libs() ->
 
335
    case os:getenv("ERL_LIBS") of
 
336
        false  -> [];
 
337
        LibStr -> string:tokens(LibStr, ":;")
 
338
    end.
 
339
 
 
340
diff_script(Script, Script) ->
 
341
    equal;
 
342
diff_script({script, Rel, Commands1}, {script, Rel, Commands2}) ->
 
343
    diff_cmds(Commands1, Commands2);
 
344
diff_script({script, Rel1, _}, {script, Rel2, _}) ->
 
345
    {error, {Rel1, Rel2}}.
 
346
 
 
347
diff_cmds([Cmd | Commands1], [Cmd | Commands2]) ->
 
348
    diff_cmds(Commands1, Commands2);
 
349
diff_cmds([Cmd1 | _Commands1], [Cmd2 | _Commands2]) ->
 
350
    {diff, {expected, Cmd1}, {actual, Cmd2}};
 
351
diff_cmds([], []) ->
 
352
    equal.
 
353
 
 
354
os_cmd(Cmd) when is_list(Cmd) ->
 
355
    %% Call the plain os:cmd with an echo command appended to print command status
 
356
    %% io:format("os:cmd(~p).\n", [Cmd]),
 
357
    case os:cmd(Cmd++";echo \"#$?\"") of
 
358
        %% There is (as far as I can tell) only one thing that will match this
 
359
        %% and that is too silly to ever be used, but...
 
360
        []->
 
361
            {99, []};
 
362
        Return->
 
363
            %% Find the position of the status code wich is last in the string
 
364
            %% prepended with #
 
365
            case string:rchr(Return, $#) of
 
366
                
 
367
                %% This happens only if the sh command pipe is somehow interrupted
 
368
                0->
 
369
                {98, Return};
 
370
                
 
371
                Position->
 
372
                Result = string:left(Return,Position - 1),
 
373
                Status = string:substr(Return,Position + 1, length(Return) - Position - 1),
 
374
                {list_to_integer(Status), Result}
 
375
            end
 
376
    end.
 
377
 
 
378
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
379
%% Node handling
 
380
 
 
381
start_node(Name, ErlPath) ->
 
382
    FullName = full_node_name(Name),
 
383
    CmdLine = mk_node_cmdline(Name, ErlPath),
 
384
    io:format("Starting node ~p: ~s~n", [FullName, CmdLine]),
 
385
    case open_port({spawn, CmdLine}, []) of
 
386
        Port when is_port(Port) ->
 
387
            unlink(Port),
 
388
            erlang:port_close(Port),
 
389
            case ping_node(FullName, 50) of
 
390
                ok -> {ok, FullName};
 
391
                Other -> exit({failed_to_start_node, FullName, Other})
 
392
            end;
 
393
        Error ->
 
394
            exit({failed_to_start_node, FullName, Error})
 
395
    end.
 
396
 
 
397
stop_node(Node) ->
 
398
    monitor_node(Node, true),
 
399
    spawn(Node, fun () -> halt() end),
 
400
    receive {nodedown, Node} -> ok end.
 
401
 
 
402
mk_node_cmdline(Name) ->
 
403
    Prog = case catch init:get_argument(progname) of
 
404
               {ok,[[P]]} -> P;
 
405
               _ -> exit(no_progname_argument_found)
 
406
           end,
 
407
    mk_node_cmdline(Name, Prog).
 
408
 
 
409
mk_node_cmdline(Name, Prog) ->
 
410
    Static = "-detached -noinput",
 
411
    Pa = filename:dirname(code:which(?MODULE)),
 
412
    NameSw = case net_kernel:longnames() of
 
413
                 false -> "-sname ";
 
414
                 true -> "-name ";
 
415
                 _ -> exit(not_distributed_node)
 
416
             end,
 
417
    {ok, Pwd} = file:get_cwd(),
 
418
    NameStr = atom_to_list(Name),
 
419
    Prog ++ " "
 
420
        ++ Static ++ " "
 
421
        ++ NameSw ++ " " ++ NameStr ++ " "
 
422
        ++ "-pa " ++ Pa ++ " "
 
423
        ++ "-env ERL_CRASH_DUMP " ++ Pwd ++ "/erl_crash_dump." ++ NameStr ++ " "
 
424
        ++ "-setcookie " ++ atom_to_list(erlang:get_cookie()).
 
425
 
 
426
full_node_name(PreName) ->
 
427
    HostSuffix = lists:dropwhile(fun ($@) -> false; (_) -> true end,
 
428
                                 atom_to_list(node())),
 
429
    list_to_atom(atom_to_list(PreName) ++ HostSuffix).
 
430
 
 
431
ping_node(_Node, 0) ->
 
432
    {error, net_adm};
 
433
ping_node(Node, N) when is_integer(N), N > 0 ->
 
434
    case catch net_adm:ping(Node) of
 
435
        pong -> 
 
436
            wait_for_process(Node, code_server, 50);
 
437
        _ ->
 
438
            timer:sleep(1000),
 
439
            ping_node(Node, N-1)
 
440
    end.
 
441
 
 
442
wait_for_process(_Node, Name, 0) ->
 
443
    {error, Name};
 
444
wait_for_process(Node, Name, N) when is_integer(N), N > 0 ->
 
445
    case rpc:call(Node, erlang, whereis, [Name]) of
 
446
        undefined ->
 
447
            timer:sleep(1000),
 
448
            wait_for_process(Node, Name, N-1);
 
449
        {badrpc, _} = Reason ->
 
450
            erlang:error({Reason, Node});
 
451
        Pid when is_pid(Pid) ->
 
452
            ok
 
453
    end.
 
454
 
 
455
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
456
%% Run escript
 
457
 
 
458
run(Dir, Cmd0) ->
 
459
    Cmd = case os:type() of
 
460
              {win32,_} -> filename:nativename(Dir) ++ "\\" ++ Cmd0;
 
461
              _ -> Cmd0
 
462
          end,
 
463
    do_run(Dir, Cmd).
 
464
 
 
465
run(Dir, Opts, Cmd0) ->
 
466
    Cmd = case os:type() of
 
467
              {win32,_} -> Opts ++ " " ++ filename:nativename(Dir) ++ "\\" ++ Cmd0;
 
468
              _ -> Opts ++ " " ++ Dir ++ "/" ++ Cmd0
 
469
          end,
 
470
    do_run(Dir, Cmd).
 
471
 
 
472
do_run(Dir, Cmd) ->
 
473
    io:format("Run: ~p\n", [Cmd]),
 
474
    Env = [{"PATH",Dir++":"++os:getenv("PATH")}],
 
475
    Port = open_port({spawn,Cmd}, [exit_status,eof,in,{env,Env}]),
 
476
    Res = get_data(Port, []),
 
477
    receive
 
478
        {Port,{exit_status,ExitCode}} ->
 
479
            iolist_to_binary([Res,"ExitCode:"++integer_to_list(ExitCode)])
 
480
    end.
 
481
 
 
482
get_data(Port, SoFar) ->
 
483
    receive
 
484
        {Port,{data,Bytes}} ->
 
485
            get_data(Port, [SoFar|Bytes]);
 
486
        {Port,eof} ->
 
487
            erlang:port_close(Port),
 
488
            SoFar
 
489
    end.
 
490
 
 
491
expected_output([data_dir|T], Data) ->
 
492
    Slash = case os:type() of
 
493
                {win32,_} -> "\\";
 
494
                _ -> "/"
 
495
            end,
 
496
    [filename:nativename(Data)++Slash|expected_output(T, Data)];
 
497
expected_output([H|T], Data) ->
 
498
    [H|expected_output(T, Data)];
 
499
expected_output([], _) -> 
 
500
    [];
 
501
expected_output(Bin, _) when is_binary(Bin) -> 
 
502
    Bin.