~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/src/escript.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
17
17
%%
18
18
-module(escript).
19
19
 
20
 
%% Useful functionst that can be called from scripts.
 
20
%% Useful functions that can be called from scripts.
21
21
-export([script_name/0]).
22
22
 
23
23
%% Internal API.
24
24
-export([start/0, start/1]).
25
25
 
26
 
-import(lists, [foldl/3,flatmap/2,member/2,reverse/1,foreach/2]).
27
 
 
28
26
script_name() ->
29
27
    [ScriptName|_] = init:get_plain_arguments(),
30
28
    ScriptName.
38
36
 
39
37
start(EscriptOptions) ->
40
38
    try 
41
 
        [File|Args] = init:get_plain_arguments(),
42
 
        do_run(File, Args, EscriptOptions)
 
39
        %% Commands run using -run or -s are run in a process
 
40
        %% trap_exit set to false. Because this behaviour is
 
41
        %% surprising for users of escript, make sure to reset
 
42
        %% trap_exit to false.
 
43
        process_flag(trap_exit, false),
 
44
        case init:get_plain_arguments() of
 
45
            [File|Args] ->
 
46
                do_run(File, Args, EscriptOptions);
 
47
            [] ->
 
48
                io:format("escript: Missing filename\n", []),
 
49
                my_halt(127)
 
50
        end
43
51
    catch
44
52
        throw:Str ->
45
53
            io:format("escript: ~s\n", [Str]),
56
64
 
57
65
do_run(File, Args, Options) ->
58
66
    {Parse,Mode} = parse_file(File),
59
 
    case Options of
60
 
        ["s"] ->
 
67
    case lists:member("s", Options) of
 
68
        true when Mode =:= run ->
 
69
            my_halt(0);
 
70
        true ->
61
71
            %% Syntax check only.
62
72
            case compile:forms(Parse, [report,strong_validation]) of
63
73
                {ok,_} ->
65
75
                _Other ->
66
76
                    fatal("There were compilation errors.")
67
77
            end;
68
 
        _ ->
 
78
        false ->
69
79
            eval_module(Mode, Parse, File, Args)
70
80
    end.
71
81
 
72
82
eval_module(interpret, Parse, File, Args) ->
73
83
    interpret(File, Parse, Args);
74
84
eval_module(compile, Parse, _File, Args) ->
75
 
    compile(Parse, Args).
 
85
    compile(Parse, Args);
 
86
eval_module(run, Module, _File, Args) ->
 
87
    run_code(Module, Args).
76
88
 
77
89
interpret(File, Parse0, Args) ->
78
90
    case erl_lint:module(Parse0) of
102
114
compile(Parse, Args) ->
103
115
    case compile:forms(Parse, [report]) of
104
116
        {ok,Module,BeamCode} -> 
105
 
            erlang:load_module(Module, BeamCode),
 
117
            {module, Module} = erlang:load_module(Module, BeamCode),
106
118
            run_code(Module, Args);
107
119
        _Other ->
108
120
            fatal("There were compilation errors.")
131
143
    Dict = dict:store({local, Name,Arity}, Clauses, Dict0),
132
144
    parse_to_dict(T, Dict);
133
145
parse_to_dict([{attribute,_,import,{Mod,Funcs}}|T], Dict0) ->
134
 
    Dict = foldl(fun(I, D) ->
135
 
                         dict:store({remote,I}, Mod, D)
136
 
                 end, Dict0, Funcs),
 
146
    Dict = lists:foldl(fun(I, D) ->
 
147
                               dict:store({remote,I}, Mod, D)
 
148
                       end, Dict0, Funcs),
137
149
    parse_to_dict(T, Dict);
138
150
parse_to_dict([_|T], Dict) ->
139
151
    parse_to_dict(T, Dict);
148
160
                       integer_to_list(K)),
149
161
    {attribute,0,module, Mod}.
150
162
 
 
163
-define(PRETTY_APPLY(M, F, A), pretty_apply(?MODULE, ?LINE, M, F, A)).
 
164
 
151
165
parse_file(File) ->
152
166
    parse_check_error(File, parse_file(File, 0, [], interpret)).
153
167
 
154
168
parse_file(File, Nerrs, L, Mode) ->
155
 
    {ok, P} = file:open(File, [read]),
156
 
    %% This is to skip the first line in the script
157
 
    io:get_line(P, ''),
158
 
    Ret = parse_loop(P, File, io:parse_erl_form(P, '', 2), Nerrs, L, Mode),
159
 
    file:close(P),
160
 
    Ret.
 
169
    {ok, P} = 
 
170
        case file:open(File, [read]) of
 
171
            {ok, P0} ->
 
172
                {ok, P0};
 
173
            {error, R} ->
 
174
                fatal(lists:concat([file:format_error(R), ": '", File, "'"]))
 
175
        end,
 
176
    {HeaderSz, BodyLineNo, FirstBodyLine} = skip_header(P),
 
177
    case FirstBodyLine of
 
178
        [$P, $K | _] ->
 
179
            %% Archive file
 
180
            ok = ?PRETTY_APPLY(file, close, [P]),
 
181
            {ok, <<_FirstLine:HeaderSz/binary, Bin/binary>>} =
 
182
                ?PRETTY_APPLY(file, read_file, [File]),
 
183
            case code:set_primary_archive(File, Bin) of
 
184
                ok ->
 
185
                    Mod = 
 
186
                        case init:get_argument(escript) of
 
187
                            {ok, [["main", M]]} -> 
 
188
                                list_to_atom(M);
 
189
                            _ -> 
 
190
                                Ext = init:archive_extension(),
 
191
                                list_to_atom(filename:basename(File, Ext))
 
192
                        end,
 
193
                    {Nerrs,Mod,run};
 
194
                {error, bad_eocd} ->
 
195
                    fatal("Not an archive file");
 
196
                {error, Reason} ->
 
197
                    fatal(Reason)
 
198
            end;
 
199
        [$F, $O, $R, $1 | _] ->
 
200
            %% Beam file
 
201
            ok = ?PRETTY_APPLY(file, close, [P]),
 
202
            {ok, <<_FirstLine:HeaderSz/binary, Bin/binary>>} =
 
203
                ?PRETTY_APPLY(file, read_file, [File]),
 
204
            case beam_lib:version(Bin) of
 
205
                {ok, {Mod, _Version}} ->
 
206
                    {module, Mod} = erlang:load_module(Mod, Bin),
 
207
                    {Nerrs,Mod,run};
 
208
                {error, beam_lib, Reason} when is_tuple(Reason) ->
 
209
                    fatal(element(1, Reason));
 
210
                {error, beam_lib, Reason} ->
 
211
                    fatal(Reason)
 
212
            end;
 
213
        _ ->
 
214
            %% Source code
 
215
            {ok, _} = ?PRETTY_APPLY(file, position, [P, {bof, HeaderSz}]), % Goto prev pos
 
216
            Ret = parse_loop(P, File, io:parse_erl_form(P, '', BodyLineNo), Nerrs, L, Mode),
 
217
            ok = ?PRETTY_APPLY(file, close, [P]),
 
218
            Ret
 
219
    end.
 
220
 
 
221
pretty_apply(Module, Line, M, F, A) ->
 
222
    case apply(M, F, A) of
 
223
        ok ->
 
224
            ok;
 
225
        {ok, Res} ->
 
226
            {ok, Res};
 
227
        {error, Reason} ->
 
228
            fatal({Module, Line, M, F, A, Reason})
 
229
    end.
 
230
            
 
231
%% Skip header and return first body line
 
232
skip_header(P) ->
 
233
    %% Skip shebang on first line
 
234
    get_line(P),
 
235
    {ok, HeaderSz1} = file:position(P, cur),
 
236
    
 
237
    %% Look for special comment on second line
 
238
    Line2 = get_line(P),
 
239
    {ok, HeaderSz2} = file:position(P, cur),
 
240
    case Line2 of
 
241
        [$\%, $\%, $\! | _] ->
 
242
            %% Skip special comment on second line
 
243
            Line3 = get_line(P),
 
244
            {HeaderSz2, 3, Line3};
 
245
         _ ->
 
246
                %% Look for special comment on third line
 
247
                Line3 = get_line(P),
 
248
                {ok, HeaderSz3} = file:position(P, cur),
 
249
                case Line3 of
 
250
                    [$\%, $\%, $\! | _] -> 
 
251
                        %% Skip special comment on third line
 
252
                        Line4 = get_line(P),
 
253
                        {HeaderSz3, 4, Line4};
 
254
                    _ ->
 
255
                        %% Just skip shebang on first line
 
256
                        {HeaderSz1, 2, Line2}
 
257
                end
 
258
    end.
 
259
    
 
260
get_line(P) ->
 
261
    case io:get_line(P, '') of
 
262
        eof ->
 
263
            fatal("Premature end of file reached");
 
264
        Line ->
 
265
            Line
 
266
    end.
161
267
 
162
268
parse_include_lib(File, Nerrs, L0, Mode) ->
163
269
    case open_lib_dir(File) of
183
289
            {error,bad_libdir}
184
290
    end.
185
291
 
 
292
parse_check_error(_File, {0,Module,Mode = run}) when is_atom(Module) ->
 
293
    {Module,Mode};
186
294
parse_check_error(File, {0,L0,Mode}) ->
187
 
    L = reverse(L0),
 
295
    L = lists:reverse(L0),
188
296
    Code = [{attribute,0,file,{File,1}},
189
297
            mk_mod()|case is_main_exported(L) of
190
298
                         false ->
193
301
                             L
194
302
                     end],
195
303
    {Code,Mode};
196
 
parse_check_error(_, _) -> fatal("There were compilation errors.").
 
304
parse_check_error(_, _) ->
 
305
    fatal("There were compilation errors.").
197
306
 
198
307
maybe_expand_records(Code) ->
199
308
    case erase(there_are_records) of
251
360
    end.
252
361
 
253
362
is_main_exported([{attribute,_,export,Fs}|T]) ->
254
 
    case member({main,1}, Fs) of
 
363
    case lists:member({main,1}, Fs) of
255
364
        false -> is_main_exported(T);
256
365
        true -> true
257
366
    end;
262
371
    throw(Str).
263
372
                                
264
373
report_errors(Errors) ->
265
 
    foreach(fun ({{F,_L},Eds}) -> list_errors(F, Eds);
266
 
                ({F,Eds}) -> list_errors(F, Eds) end,
267
 
            Errors).
 
374
    lists:foreach(fun ({{F,_L},Eds}) -> list_errors(F, Eds);
 
375
                      ({F,Eds}) -> list_errors(F, Eds) end,
 
376
                  Errors).
268
377
 
269
378
list_errors(F, [{Line,Mod,E}|Es]) ->
270
379
    io:fwrite("~s:~w: ~s\n", [F,Line,Mod:format_error(E)]),
275
384
list_errors(_F, []) -> ok.
276
385
 
277
386
report_warnings(Ws0) ->
278
 
    Ws1 = flatmap(fun({{F,_L},Eds}) -> format_message(F, Eds);
279
 
                     ({F,Eds}) -> format_message(F, Eds) end,
 
387
    Ws1 = lists:flatmap(fun({{F,_L},Eds}) -> format_message(F, Eds);
 
388
                           ({F,Eds}) -> format_message(F, Eds) end,
280
389
                  Ws0),
281
390
    Ws = ordsets:from_list(Ws1),
282
 
    foreach(fun({_,Str}) -> io:put_chars(Str) end, Ws).
 
391
    lists:foreach(fun({_,Str}) -> io:put_chars(Str) end, Ws).
283
392
 
284
393
format_message(F, [{Line,Mod,E}|Es]) ->
285
394
    M = {{F,Line},io_lib:format("~s:~w: Warning: ~s\n", [F,Line,Mod:format_error(E)])},