~statik/ubuntu/maverick/erlang/erlang-merge-testing

« 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-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 2002, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
17
 
%%
 
17
%% %CopyrightEnd%
 
18
 
18
19
-module(escript).
19
20
 
20
21
%% Useful functions that can be called from scripts.
21
 
-export([script_name/0]).
 
22
-export([script_name/0, foldl/3]).
22
23
 
23
24
%% Internal API.
24
25
-export([start/0, start/1]).
25
26
 
 
27
-record(state, {file,
 
28
                module,
 
29
                forms_or_bin,
 
30
                source,
 
31
                n_errors,
 
32
                mode,
 
33
                exports_main,
 
34
                has_records}).
 
35
    
26
36
script_name() ->
27
37
    [ScriptName|_] = init:get_plain_arguments(),
28
38
    ScriptName.
29
39
 
 
40
%% Apply Fun(Name, GetInfo, GetBin, Acc) for each file in the escript.
 
41
%% 
 
42
%% Fun/2 must return a new accumulator which is passed to the next call.
 
43
%% The function returns the final value of the accumulator. Acc0 is
 
44
%% returned if the escript contain an empty archive.
 
45
%% 
 
46
%% GetInfo/0 is a fun that returns a #file_info{} record for the file.
 
47
%% GetBin/0 is a fun that returns a the contents of the file as a binary.
 
48
%%
 
49
%% An escript may contain erlang code, beam code or an archive:
 
50
%%
 
51
%% archive - the Fun/2 will be applied for each file in the archive
 
52
%% beam - the Fun/2 will be applied once and GetInfo/0 returns the file
 
53
%%        info for the (entire) escript file
 
54
%% erl - the Fun/2 will be applied once, GetInfo/0 returns the file
 
55
%%       info for the (entire) escript file and the GetBin returns
 
56
%%       the compiled beam code
 
57
 
 
58
%%-spec foldl(fun((string(),
 
59
%%                 fun(() -> #file_info()), 
 
60
%%                 fun(() -> binary() -> term()),
 
61
%%                 term()) -> term()),
 
62
%%            term(),
 
63
%%            string()).
 
64
foldl(Fun, Acc0, File) when is_function(Fun, 4) ->
 
65
    case parse_file(File, false) of
 
66
        {text, _, Forms, _Mode} when is_list(Forms) ->
 
67
            GetInfo = fun() -> file:read_file_info(File) end,
 
68
            GetBin =
 
69
                fun() ->
 
70
                        case compile:forms(Forms, [return_errors, debug_info]) of
 
71
                            {ok, _, BeamBin} ->
 
72
                                BeamBin;
 
73
                            {error, _Errors, _Warnings} ->
 
74
                                fatal("There were compilation errors.")
 
75
                        end
 
76
                end,
 
77
            try
 
78
                {ok, Fun(".", GetInfo, GetBin, Acc0)}
 
79
            catch
 
80
                throw:Reason ->
 
81
                    {error, Reason}
 
82
            end;
 
83
        {beam, _, BeamBin, _Mode} when is_binary(BeamBin) ->
 
84
            GetInfo = fun() -> file:read_file_info(File) end,
 
85
            GetBin = fun() -> BeamBin end,
 
86
            try
 
87
                {ok, Fun(".", GetInfo, GetBin, Acc0)}
 
88
            catch
 
89
                throw:Reason ->
 
90
                    {error, Reason}
 
91
            end;
 
92
        {archive, _, ArchiveBin, _Mode} when is_binary(ArchiveBin) ->
 
93
            ZipFun =
 
94
                fun({Name, GetInfo, GetBin}, A) ->
 
95
                        A2 = Fun(Name, GetInfo, GetBin, A),
 
96
                        {true, false, A2}
 
97
                end,
 
98
            case prim_zip:open(ZipFun, Acc0, {File, ArchiveBin}) of
 
99
                {ok, PrimZip, Res} ->
 
100
                    ok = prim_zip:close(PrimZip),
 
101
                    {ok, Res};
 
102
                {error, bad_eocd} ->
 
103
                    {error, "Not an archive file"};
 
104
                {error, Reason} ->
 
105
                    {error, Reason}
 
106
            end
 
107
    end.
 
108
 
30
109
%%
31
110
%% Internal API.
32
111
%%
36
115
 
37
116
start(EscriptOptions) ->
38
117
    try 
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
51
 
    catch
52
 
        throw:Str ->
53
 
            io:format("escript: ~s\n", [Str]),
54
 
            my_halt(127);
55
 
        _:Reason ->
56
 
            io:format("escript: Internal error: ~p\n", [Reason]),
57
 
            io:format("~p\n", [erlang:get_stacktrace()]),
58
 
            my_halt(127)
59
 
    end.
60
 
 
61
 
%%%
62
 
%%% Internal functions follow.
63
 
%%%
64
 
 
65
 
do_run(File, Args, Options) ->
66
 
    {Parse,Mode} = parse_file(File),
67
 
    case lists:member("s", Options) of
68
 
        true when Mode =:= run ->
69
 
            my_halt(0);
70
 
        true ->
71
 
            %% Syntax check only.
72
 
            case compile:forms(Parse, [report,strong_validation]) of
73
 
                {ok,_} ->
74
 
                    my_halt(0);
75
 
                _Other ->
76
 
                    fatal("There were compilation errors.")
77
 
            end;
78
 
        false ->
79
 
            eval_module(Mode, Parse, File, Args)
80
 
    end.
81
 
 
82
 
eval_module(interpret, Parse, File, Args) ->
83
 
    interpret(File, Parse, Args);
84
 
eval_module(compile, Parse, _File, Args) ->
85
 
    compile(Parse, Args);
86
 
eval_module(run, Module, _File, Args) ->
87
 
    run_code(Module, Args).
88
 
 
89
 
interpret(File, Parse0, Args) ->
90
 
    case erl_lint:module(Parse0) of
91
 
        {ok,Ws} ->
92
 
            report_warnings(Ws);
93
 
        {error,Es,Ws} ->
94
 
            report_errors(Es),
95
 
            report_warnings(Ws),
96
 
            fatal("There were compilation errors.")
97
 
    end,
98
 
    Parse = maybe_expand_records(Parse0),
99
 
    Dict  = parse_to_dict(Parse),
100
 
    ArgsA = erl_parse:abstract(Args, 0),
101
 
    Call = {call,0,{atom,0,main},[ArgsA]},
102
 
    try
103
 
        erl_eval:expr(Call,
104
 
                      erl_eval:new_bindings(),
105
 
                      {value,fun(I, J) ->
106
 
                                     code_handler(I, J, Dict, File)
107
 
                             end}),
108
 
        my_halt(0)
109
 
    catch
110
 
        Class:Reason ->
111
 
            fatal(format_exception(Class, Reason))
112
 
    end.
113
 
 
114
 
compile(Parse, Args) ->
115
 
    case compile:forms(Parse, [report]) of
116
 
        {ok,Module,BeamCode} -> 
117
 
            {module, Module} = erlang:load_module(Module, BeamCode),
118
 
            run_code(Module, Args);
119
 
        _Other ->
120
 
            fatal("There were compilation errors.")
121
 
    end.
122
 
 
123
 
run_code(Module, Args) ->
124
 
    try
125
 
        Module:main(Args),
126
 
        my_halt(0)
127
 
    catch
128
 
        Class:Reason ->
129
 
            fatal(format_exception(Class, Reason))
130
 
    end.
131
 
 
132
 
format_exception(Class, Reason) ->
133
 
    PF = fun(Term, I) -> 
134
 
                 io_lib:format("~." ++ integer_to_list(I) ++ "P", [Term, 50]) 
135
 
         end,
136
 
    StackTrace = erlang:get_stacktrace(),
137
 
    StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end,
138
 
    lib:format_exception(1, Class, Reason, StackTrace, StackFun, PF).
139
 
 
140
 
parse_to_dict(L) -> parse_to_dict(L, dict:new()).
141
 
 
142
 
parse_to_dict([{function,_,Name,Arity,Clauses}|T], Dict0) ->
143
 
    Dict = dict:store({local, Name,Arity}, Clauses, Dict0),
144
 
    parse_to_dict(T, Dict);
145
 
parse_to_dict([{attribute,_,import,{Mod,Funcs}}|T], Dict0) ->
146
 
    Dict = lists:foldl(fun(I, D) ->
147
 
                               dict:store({remote,I}, Mod, D)
148
 
                       end, Dict0, Funcs),
149
 
    parse_to_dict(T, Dict);
150
 
parse_to_dict([_|T], Dict) ->
151
 
    parse_to_dict(T, Dict);
152
 
parse_to_dict([], Dict) ->
153
 
    Dict.
154
 
 
155
 
%% make a temporary module name
156
 
 
157
 
mk_mod() ->
158
 
    {I,J,K} = erlang:now(),
159
 
    Mod = list_to_atom("escript__" ++ integer_to_list(I) ++ integer_to_list(J) ++
160
 
                       integer_to_list(K)),
161
 
    {attribute,0,module, Mod}.
162
 
 
163
 
-define(PRETTY_APPLY(M, F, A), pretty_apply(?MODULE, ?LINE, M, F, A)).
164
 
 
165
 
parse_file(File) ->
166
 
    parse_check_error(File, parse_file(File, 0, [], interpret)).
167
 
 
168
 
parse_file(File, Nerrs, L, Mode) ->
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
 
            
 
118
        %% Commands run using -run or -s are run in a process
 
119
        %% trap_exit set to false. Because this behaviour is
 
120
        %% surprising for users of escript, make sure to reset
 
121
        %% trap_exit to false.
 
122
        process_flag(trap_exit, false),
 
123
        case init:get_plain_arguments() of
 
124
            [File|Args] ->
 
125
                parse_and_run(File, Args, EscriptOptions);
 
126
            [] ->
 
127
                io:format("escript: Missing filename\n", []),
 
128
                my_halt(127)
 
129
        end
 
130
    catch
 
131
        throw:Str ->
 
132
            io:format("escript: ~s\n", [Str]),
 
133
            my_halt(127);
 
134
        _:Reason ->
 
135
            io:format("escript: Internal error: ~p\n", [Reason]),
 
136
            io:format("~p\n", [erlang:get_stacktrace()]),
 
137
            my_halt(127)
 
138
    end.
 
139
 
 
140
parse_and_run(File, Args, Options) ->
 
141
    CheckOnly = lists:member("s", Options),
 
142
    {Source, Module, FormsOrBin, Mode} = parse_file(File, CheckOnly),
 
143
    Mode2 =
 
144
        case lists:member("d", Options) of
 
145
            true  -> 
 
146
                debug;
 
147
            false ->
 
148
                case lists:member("c", Options) of
 
149
                    true  -> 
 
150
                        compile;
 
151
                    false ->
 
152
                        case lists:member("i", Options) of
 
153
                            true  -> interpret;
 
154
                            false -> Mode
 
155
                        end
 
156
                end
 
157
        end,
 
158
    if
 
159
        is_list(FormsOrBin) ->
 
160
            case Mode2 of
 
161
                interpret ->
 
162
                    interpret(FormsOrBin, File, Args);
 
163
                compile ->
 
164
                    case compile:forms(FormsOrBin, [report]) of
 
165
                        {ok, Module, BeamBin} ->
 
166
                            {module, Module} = code:load_binary(Module, File, BeamBin),
 
167
                            run(Module, Args);
 
168
                        _Other ->
 
169
                            fatal("There were compilation errors.")
 
170
                    end;
 
171
                debug ->
 
172
                    case compile:forms(FormsOrBin, [report, debug_info]) of
 
173
                        {ok,Module,BeamBin} ->
 
174
                            {module, Module} = code:load_binary(Module, File, BeamBin),
 
175
                            debug(Module, {Module, File, File, BeamBin}, Args);
 
176
                        _Other ->
 
177
                            fatal("There were compilation errors.")
 
178
                    end
 
179
            end;                    
 
180
        is_binary(FormsOrBin) ->
 
181
            case Source of
 
182
                archive ->
 
183
                    case code:set_primary_archive(File, FormsOrBin) of
 
184
                        ok when CheckOnly ->
 
185
                            case code:load_file(Module) of
 
186
                                {module, _} ->
 
187
                                    case erlang:function_exported(Module, main, 1) of
 
188
                                        true ->
 
189
                                            my_halt(0);
 
190
                                        false ->
 
191
                                            Text = lists:concat(["Function ", Module, ":main/1 is not exported"]),
 
192
                                            fatal(Text)
 
193
                                    end;
 
194
                                _ ->
 
195
                                    Text = lists:concat(["Cannot load module ", Module, " from archive"]),
 
196
                                    fatal(Text)
 
197
                            end;
 
198
                        ok ->
 
199
                            case Mode2 of
 
200
                                run   -> run(Module, Args);
 
201
                                debug -> debug(Module, Module, Args)
 
202
                            end;
 
203
                        {error, bad_eocd} ->
 
204
                            fatal("Not an archive file");
 
205
                        {error, Reason} ->
 
206
                            fatal(Reason)
 
207
                    end;
 
208
                beam ->
 
209
                    case Mode2 of
 
210
                        run ->
 
211
                            {module, Module} = code:load_binary(Module, File, FormsOrBin),
 
212
                            run(Module, Args);
 
213
                        debug -> 
 
214
                            [Base | Rest] = lists:reverse(filename:split(File)),
 
215
                            Base2 = filename:basename(Base, code:objfile_extension()),
 
216
                            Rest2 =
 
217
                                case Rest of
 
218
                                    ["ebin" | Top] -> ["src" | Top];
 
219
                                    _ -> Rest
 
220
                                end,
 
221
                            SrcFile = filename:join(lists:reverse([Base2 ++ ".erl" | Rest2])),
 
222
                            debug(Module, {Module, SrcFile, File, FormsOrBin}, Args)
 
223
                    end             
 
224
            end             
 
225
    end.
 
226
 
 
227
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
228
%% Parse script
 
229
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
230
 
 
231
parse_file(File, CheckOnly) ->
 
232
    S = #state{file = File,
 
233
               n_errors = 0,
 
234
               mode = interpret,
 
235
               exports_main = false,
 
236
               has_records = false},
 
237
    {ok, Fd} = 
 
238
        case file:open(File, [read]) of
 
239
            {ok, Fd0} ->
 
240
                {ok, Fd0};
 
241
            {error, R} ->
 
242
                fatal(lists:concat([file:format_error(R), ": '", File, "'"]))
 
243
        end,
 
244
    {HeaderSz, StartLine, FirstBodyLine} = skip_header(Fd, 1),
 
245
    #state{mode = Mode,
 
246
           source = Source,
 
247
           module = Module,
 
248
           forms_or_bin = FormsOrBin} =
 
249
        case FirstBodyLine of
 
250
            [$P, $K | _] ->
 
251
                %% Archive file
 
252
                ok = file:close(Fd),
 
253
                parse_archive(S, File, HeaderSz);
 
254
            [$F, $O, $R, $1 | _] ->
 
255
                %% Beam file
 
256
                ok = file:close(Fd),
 
257
                parse_beam(S, File, HeaderSz, CheckOnly);
 
258
            _ ->
 
259
                %% Source code
 
260
                parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly)
 
261
        end,
 
262
    {Source, Module, FormsOrBin, Mode}.
 
263
 
231
264
%% Skip header and return first body line
232
 
skip_header(P) ->
 
265
skip_header(P, LineNo) ->
233
266
    %% 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
 
267
    {ok, HeaderSz0} = file:position(P, cur),
 
268
    Line1 = get_line(P),
 
269
    case Line1 of
 
270
        [$\#, $\! | _] ->
 
271
            %% Shebang
 
272
            {ok, HeaderSz1} = file:position(P, cur),
 
273
            
 
274
            %% Look for special comment on second line
 
275
            Line2 = get_line(P),
 
276
            {ok, HeaderSz2} = file:position(P, cur),
 
277
            case Line2 of
 
278
                [$\%, $\%, $\! | _] ->
 
279
                    %% Skip special comment on second line
 
280
                    Line3 = get_line(P),
 
281
                    {HeaderSz2, LineNo + 2, Line3};
 
282
                _ ->
 
283
                    %% Look for special comment on third line
 
284
                    Line3 = get_line(P),
 
285
                    {ok, HeaderSz3} = file:position(P, cur),
 
286
                    case Line3 of
 
287
                        [$\%, $\%, $\! | _] -> 
 
288
                            %% Skip special comment on third line
 
289
                            Line4 = get_line(P),
 
290
                            {HeaderSz3, LineNo + 3, Line4};
 
291
                        _ ->
 
292
                            %% Just skip shebang on first line
 
293
                            {HeaderSz1, LineNo + 1, Line2}
 
294
                    end
 
295
            end;
 
296
        _ ->
 
297
            %% No shebang. Assume that there is no header.
 
298
            {HeaderSz0, LineNo, Line1}
258
299
    end.
259
300
    
260
301
get_line(P) ->
261
302
    case io:get_line(P, '') of
262
 
        eof ->
263
 
            fatal("Premature end of file reached");
264
 
        Line ->
265
 
            Line
266
 
    end.
267
 
 
268
 
parse_include_lib(File, Nerrs, L0, Mode) ->
269
 
    case open_lib_dir(File) of
270
 
        {ok,P} ->
271
 
            L = [{attribute,1,file,{File,1}}|L0],
272
 
            Ret = parse_loop(P, File, io:parse_erl_form(P, '', 1), Nerrs, L, Mode),
273
 
            file:close(P),
274
 
            Ret;
275
 
        {error,bad_libdir} ->
276
 
            io:format("Misformed -include_lib");
277
 
        {error,Reason} ->
278
 
            io:format("Failed to open ~s: ~s\n", [File,file:format_error(Reason)]),
279
 
            {Nerrs,L0,Mode}
280
 
    end.
281
 
 
282
 
open_lib_dir(File0) ->
283
 
    try
284
 
        [LibName|Rest] = filename:split(File0),
285
 
        File = filename:join([code:lib_dir(list_to_atom(LibName))|Rest]),
286
 
        file:open(File, [read])
287
 
    catch
288
 
        _:_ ->
289
 
            {error,bad_libdir}
290
 
    end.
291
 
 
292
 
parse_check_error(_File, {0,Module,Mode = run}) when is_atom(Module) ->
293
 
    {Module,Mode};
294
 
parse_check_error(File, {0,L0,Mode}) ->
295
 
    L = lists:reverse(L0),
296
 
    Code = [{attribute,0,file,{File,1}},
297
 
            mk_mod()|case is_main_exported(L) of
298
 
                         false ->
299
 
                             [{attribute,0,export,[{main,1}]}|L];
300
 
                         true ->
301
 
                             L
302
 
                     end],
303
 
    {Code,Mode};
304
 
parse_check_error(_, _) ->
305
 
    fatal("There were compilation errors.").
306
 
 
307
 
maybe_expand_records(Code) ->
308
 
    case erase(there_are_records) of
309
 
        true -> erl_expand_records:module(Code, []);
310
 
        _ -> Code
311
 
    end.
312
 
 
313
 
parse_loop(_, _File, {eof,_}, Nerrs, L, Mode) ->
314
 
    {Nerrs,L,Mode};
315
 
parse_loop(P, File, {ok, Form, Ln}, Nerrs0, L0, Mode0) ->
316
 
    case Form of
317
 
        {attribute,_,mode,compile} ->
318
 
            parse_loop(P, File, io:parse_erl_form(P,'',Ln), Nerrs0, L0, compile);
319
 
        {attribute,_,include_lib,Include} ->
320
 
            {Nerrs,L1,Mode} = parse_include_lib(Include, Nerrs0, L0, Mode0),
321
 
            L2 = [{attribute,Ln+1,file,{File,Ln+1}}|L1],
322
 
            parse_loop(P, File, io:parse_erl_form(P,'',Ln), Nerrs, L2, Mode);
323
 
        {attribute,_,record,_} ->
324
 
            put(there_are_records, true),
325
 
            parse_loop(P, File, io:parse_erl_form(P,'',Ln), Nerrs0, [Form|L0], Mode0);
326
 
        Form ->
327
 
            parse_loop(P, File, io:parse_erl_form(P,'',Ln), Nerrs0, [Form|L0], Mode0)
328
 
    end;
329
 
parse_loop(P, File, {error,{Ln,Mod,Args}, Ln1}, Nerrs, L, Mode) ->
330
 
    io:format("~s:~w: ~s\n",
331
 
              [File,Ln,Mod:format_error(Args)]),
332
 
    parse_loop(P, File, io:parse_erl_form(P, '', Ln1), Nerrs+1, L, Mode).
333
 
    
334
 
code_handler(local, [file], _, File) ->
335
 
    File;
336
 
code_handler(Name, Args, Dict, File) ->
337
 
    %%io:format("code handler=~p~n",[{Name, Args}]),
338
 
    Arity = length(Args),
339
 
    case dict:find({local,Name,Arity}, Dict) of
340
 
        {ok, Cs} ->
341
 
            LF = {value,fun(I, J) ->
342
 
                                code_handler(I, J, Dict, File)
343
 
                        end},
344
 
            case erl_eval:match_clause(Cs, Args,erl_eval:new_bindings(),LF) of
345
 
                {Body, Bs} ->
346
 
                    {value, Val, _Bs1} = erl_eval:exprs(Body, Bs, LF),
347
 
                    Val;
348
 
                nomatch ->
349
 
                    erlang:error({function_clause,[{local,Name,Args}]})
 
303
        eof ->
 
304
            fatal("Premature end of file reached");
 
305
        Line ->
 
306
            Line
 
307
    end.
 
308
 
 
309
parse_archive(S, File, HeaderSz) ->
 
310
    case file:read_file(File) of
 
311
        {ok, <<_FirstLine:HeaderSz/binary, Bin/binary>>} ->
 
312
            Mod = 
 
313
                case init:get_argument(escript) of
 
314
                    {ok, [["main", M]]} ->
 
315
                        %% Use explicit module name
 
316
                        list_to_atom(M);
 
317
                    _ ->
 
318
                        %% Use escript name without extension as module name
 
319
                        RevBase = lists:reverse(filename:basename(File)),
 
320
                        RevBase2 = 
 
321
                            case lists:dropwhile(fun(X) -> X =/= $. end, RevBase) of
 
322
                                [$. | Rest] -> Rest;
 
323
                                [] -> RevBase
 
324
                            end,
 
325
                        list_to_atom(lists:reverse(RevBase2))
 
326
                end,
 
327
            
 
328
            S#state{source = archive,
 
329
                    mode = run,
 
330
                    module = Mod,
 
331
                    forms_or_bin = Bin};
 
332
        {ok, _} ->
 
333
            fatal("Illegal archive format");
 
334
        {error, Reason} ->
 
335
            fatal(file:format_error(Reason))
 
336
    end.
 
337
 
 
338
 
 
339
parse_beam(S, File, HeaderSz, CheckOnly) ->
 
340
    {ok, <<_FirstLine:HeaderSz/binary, Bin/binary>>} =
 
341
        file:read_file(File),
 
342
    case beam_lib:chunks(Bin, [exports]) of
 
343
        {ok, {Module, [{exports, Exports}]}} ->
 
344
            case CheckOnly of
 
345
                true ->
 
346
                    case lists:member({main, 1}, Exports) of
 
347
                        true ->
 
348
                            my_halt(0);
 
349
                        false ->
 
350
                            Text = lists:concat(["Function ", Module, ":main/1 is not exported"]),
 
351
                            fatal(Text)
 
352
                    end;
 
353
                false ->
 
354
                    S#state{source = beam,
 
355
                            mode = run,
 
356
                            module = Module,
 
357
                            forms_or_bin = Bin}
350
358
            end;
351
 
        error ->
352
 
            case dict:find({remote,{Name,Arity}}, Dict) of
353
 
                {ok, Mod} ->
354
 
                    %% io:format("Calling:~p~n",[{Mod,Name,Args}]),
355
 
                    apply(Mod, Name, Args);
 
359
        {error, beam_lib, Reason} when is_tuple(Reason) ->
 
360
            fatal(element(1, Reason));
 
361
        {error, beam_lib, Reason} ->
 
362
            fatal(Reason)
 
363
    end.
 
364
 
 
365
parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) ->
 
366
    {PreDefMacros, Module} = pre_def_macros(File),
 
367
    IncludePath = [],
 
368
    {ok, _} = file:position(Fd, {bof, HeaderSz}),
 
369
    case epp:open(File, Fd, StartLine, IncludePath, PreDefMacros) of
 
370
        {ok, Epp} ->
 
371
            {ok, FileForm} = epp:parse_erl_form(Epp),
 
372
            OptModRes = epp:parse_erl_form(Epp),
 
373
            S2 = S#state{source = text, module = Module},
 
374
            S3 = 
 
375
                case OptModRes of
 
376
                    {ok, {attribute,_, module, M} = Form} ->
 
377
                        epp_parse_file(Epp, S2#state{module = M}, [Form, FileForm]);
 
378
                    {ok, _} ->
 
379
                        ModForm = {attribute,1,module, Module},
 
380
                        epp_parse_file2(Epp, S2, [ModForm, FileForm], OptModRes);
 
381
                    {error, _} ->
 
382
                        epp_parse_file2(Epp, S2, [FileForm], OptModRes);
 
383
                    {eof,LastLine} ->
 
384
                        S#state{forms_or_bin = [FileForm, {eof,LastLine}]}
 
385
                end,
 
386
            ok = epp:close(Epp),
 
387
            ok = file:close(Fd),
 
388
            check_source(S3, CheckOnly);
 
389
        {error, Reason} ->
 
390
            io:format("escript: ~p\n", [Reason]),
 
391
            fatal("Preprocessor error")
 
392
    end.
 
393
 
 
394
check_source(S, CheckOnly) ->
 
395
    case S of
 
396
        #state{n_errors = Nerrs} when Nerrs =/= 0 ->
 
397
            fatal("There were compilation errors.");
 
398
        #state{exports_main = ExpMain, 
 
399
               has_records = HasRecs,
 
400
               forms_or_bin = [FileForm2, ModForm2 | Forms]} ->
 
401
            %% Optionally add export of main/1
 
402
            Forms2 =
 
403
                case ExpMain of
 
404
                    false -> [{attribute,0,export, [{main,1}]} | Forms];
 
405
                    true  -> Forms
 
406
                end,
 
407
            Forms3 = [FileForm2, ModForm2 | Forms2],
 
408
            case CheckOnly of
 
409
                true ->
 
410
                    %% Optionally expand records
 
411
                    Forms4 =
 
412
                        case HasRecs of
 
413
                            false -> Forms3;
 
414
                            true  -> erl_expand_records:module(Forms3, [])
 
415
                        end,
 
416
                    %% Strong validation and halt
 
417
                    case compile:forms(Forms4, [report,strong_validation]) of
 
418
                        {ok,_} ->
 
419
                            my_halt(0);
 
420
                        _Other ->
 
421
                            fatal("There were compilation errors.")
 
422
                    end;
 
423
                false ->
 
424
                    %% Basic validation before execution
 
425
                    case erl_lint:module(Forms3) of
 
426
                        {ok,Ws} ->
 
427
                            report_warnings(Ws);
 
428
                        {error,Es,Ws} ->
 
429
                            report_errors(Es),
 
430
                            report_warnings(Ws),
 
431
                            fatal("There were compilation errors.")
 
432
                    end,
 
433
                    %% Optionally expand records
 
434
                    Forms4 =
 
435
                        case HasRecs of
 
436
                            false -> Forms3;
 
437
                            true  -> erl_expand_records:module(Forms3, [])
 
438
                        end,
 
439
                    S#state{forms_or_bin = Forms4}
 
440
            end
 
441
    end.
 
442
 
 
443
pre_def_macros(File) ->
 
444
    {MegaSecs, Secs, MicroSecs} = erlang:now(),
 
445
    ModuleStr =
 
446
        "escript__" ++
 
447
        filename:basename(File) ++ "__" ++              
 
448
        integer_to_list(MegaSecs) ++ "__" ++
 
449
        integer_to_list(Secs) ++ "__" ++
 
450
        integer_to_list(MicroSecs),
 
451
    Module = list_to_atom(ModuleStr),
 
452
    PreDefMacros = [{'MODULE', Module, redefine},
 
453
                    {'MODULE_STRING', ModuleStr, redefine}],
 
454
    {PreDefMacros, Module}.
 
455
 
 
456
epp_parse_file(Epp, S, Forms) ->
 
457
    Parsed = epp:parse_erl_form(Epp),
 
458
    epp_parse_file2(Epp, S, Forms, Parsed).
 
459
 
 
460
epp_parse_file2(Epp, S, Forms, Parsed) ->
 
461
    %% io:format("~p\n", [Parsed]),
 
462
    case Parsed of
 
463
        {ok, Form} ->
 
464
            case Form of
 
465
                {attribute,Ln,record,{Record,Fields}} ->
 
466
                    S2 = S#state{has_records = true},
 
467
                    case epp:normalize_typed_record_fields(Fields) of
 
468
                        {typed, NewFields} ->
 
469
                            epp_parse_file(Epp, S2,
 
470
                                           [{attribute, Ln, record, {Record, NewFields}},
 
471
                                            {attribute, Ln, type, 
 
472
                                             {{record, Record}, Fields, []}} | Forms]);
 
473
                        not_typed ->
 
474
                            epp_parse_file(Epp, S2, [Form | Forms])
 
475
                    end;
 
476
                {attribute,Ln,mode,NewMode} ->
 
477
                    S2 = S#state{mode = NewMode},
 
478
                    if
 
479
                        NewMode =:= compile; NewMode =:= interpret; NewMode =:= debug ->
 
480
                            epp_parse_file(Epp, S2, [Form | Forms]);
 
481
                        true ->
 
482
                            Args = lists:flatten(io_lib:format("illegal mode attribute: ~p", [NewMode])),
 
483
                            io:format("~s:~w ~s\n", [S#state.file,Ln,Args]),
 
484
                            Error = {error,{Ln,erl_parse,Args}},
 
485
                            Nerrs= S#state.n_errors + 1,
 
486
                            epp_parse_file(Epp, S2#state{n_errors = Nerrs}, [Error | Forms])
 
487
                    end;
 
488
                {attribute,_,export,Fs} ->
 
489
                    case lists:member({main,1}, Fs) of
 
490
                        false ->
 
491
                            epp_parse_file(Epp, S, [Form | Forms]);
 
492
                        true ->
 
493
                            epp_parse_file(Epp, S#state{exports_main = true}, [Form | Forms])
 
494
                    end;
 
495
                _ ->
 
496
                    epp_parse_file(Epp, S, [Form | Forms])
 
497
            end;
 
498
        {error,{Ln,Mod,Args}} = Form ->
 
499
            io:format("~s:~w: ~s\n",
 
500
                      [S#state.file,Ln,Mod:format_error(Args)]),
 
501
            epp_parse_file(Epp, S#state{n_errors = S#state.n_errors + 1}, [Form | Forms]);
 
502
        {eof,LastLine} ->
 
503
            S#state{forms_or_bin = lists:reverse([{eof, LastLine} | Forms])}
 
504
    end.
 
505
 
 
506
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
507
%% Evaluate script
 
508
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
509
 
 
510
debug(Module, AbsMod, Args) ->
 
511
    case hidden_apply(debugger, debugger, start, []) of
 
512
        {ok, _} ->
 
513
            case hidden_apply(debugger, int, i, [AbsMod]) of
 
514
                {module, _} ->
 
515
                    hidden_apply(debugger, debugger, auto_attach, [[init]]),
 
516
                    run(Module, Args);
356
517
                error ->
357
 
                    io:format("Script does not export ~w/~w\n", [Name,Arity]),
358
 
                    my_halt(127)
359
 
            end
360
 
    end.
361
 
 
362
 
is_main_exported([{attribute,_,export,Fs}|T]) ->
363
 
    case lists:member({main,1}, Fs) of
364
 
        false -> is_main_exported(T);
365
 
        true -> true
366
 
    end;
367
 
is_main_exported([_|T]) -> is_main_exported(T);
368
 
is_main_exported([]) -> false.
369
 
 
370
 
fatal(Str) ->
371
 
    throw(Str).
372
 
                                
 
518
                    Text = lists:concat(["Cannot load the code for ", Module, " into the debugger"]),
 
519
                    fatal(Text)
 
520
            end;
 
521
        _ ->
 
522
            fatal("Cannot start the debugger")
 
523
    end.
 
524
 
 
525
run(Module, Args) ->
 
526
    try
 
527
        Module:main(Args),
 
528
        my_halt(0)
 
529
    catch
 
530
        Class:Reason ->
 
531
            fatal(format_exception(Class, Reason))
 
532
    end.
 
533
 
 
534
interpret(Forms, File, Args) ->
 
535
    Dict  = parse_to_dict(Forms),
 
536
    ArgsA = erl_parse:abstract(Args, 0),
 
537
    Call = {call,0,{atom,0,main},[ArgsA]},
 
538
    try
 
539
        erl_eval:expr(Call,
 
540
                      erl_eval:new_bindings(),
 
541
                      {value,fun(I, J) -> code_handler(I, J, Dict, File) end}),
 
542
        my_halt(0)
 
543
    catch
 
544
        Class:Reason ->
 
545
            fatal(format_exception(Class, Reason))
 
546
    end.
 
547
 
373
548
report_errors(Errors) ->
374
549
    lists:foreach(fun ({{F,_L},Eds}) -> list_errors(F, Eds);
375
 
                      ({F,Eds}) -> list_errors(F, Eds) end,
376
 
                  Errors).
 
550
                      ({F,Eds}) -> list_errors(F, Eds) end,
 
551
                  Errors).
377
552
 
378
553
list_errors(F, [{Line,Mod,E}|Es]) ->
379
554
    io:fwrite("~s:~w: ~s\n", [F,Line,Mod:format_error(E)]),
385
560
 
386
561
report_warnings(Ws0) ->
387
562
    Ws1 = lists:flatmap(fun({{F,_L},Eds}) -> format_message(F, Eds);
388
 
                           ({F,Eds}) -> format_message(F, Eds) end,
389
 
                  Ws0),
 
563
                           ({F,Eds}) -> format_message(F, Eds) end,
 
564
                  Ws0),
390
565
    Ws = ordsets:from_list(Ws1),
391
566
    lists:foreach(fun({_,Str}) -> io:put_chars(Str) end, Ws).
392
567
 
398
573
    [M|format_message(F, Es)];
399
574
format_message(_, []) -> [].
400
575
 
 
576
parse_to_dict(L) -> parse_to_dict(L, dict:new()).
 
577
 
 
578
parse_to_dict([{function,_,Name,Arity,Clauses}|T], Dict0) ->
 
579
    Dict = dict:store({local, Name,Arity}, Clauses, Dict0),
 
580
    parse_to_dict(T, Dict);
 
581
parse_to_dict([{attribute,_,import,{Mod,Funcs}}|T], Dict0) ->
 
582
    Dict = lists:foldl(fun(I, D) ->
 
583
                               dict:store({remote,I}, Mod, D)
 
584
                       end, Dict0, Funcs),
 
585
    parse_to_dict(T, Dict);
 
586
parse_to_dict([_|T], Dict) ->
 
587
    parse_to_dict(T, Dict);
 
588
parse_to_dict([], Dict) ->
 
589
    Dict.
 
590
 
 
591
code_handler(local, [file], _, File) ->
 
592
    File;
 
593
code_handler(Name, Args, Dict, File) ->
 
594
    %%io:format("code handler=~p~n",[{Name, Args}]),
 
595
    Arity = length(Args),
 
596
    case dict:find({local,Name,Arity}, Dict) of
 
597
        {ok, Cs} ->
 
598
            LF = {value,fun(I, J) -> code_handler(I, J, Dict, File) end},
 
599
            case erl_eval:match_clause(Cs, Args,erl_eval:new_bindings(),LF) of
 
600
                {Body, Bs} ->
 
601
                    {value, Val, _Bs1} = erl_eval:exprs(Body, Bs, LF),
 
602
                    Val;
 
603
                nomatch ->
 
604
                    erlang:error({function_clause,[{local,Name,Args}]})
 
605
            end;
 
606
        error ->
 
607
            case dict:find({remote,{Name,Arity}}, Dict) of
 
608
                {ok, Mod} ->
 
609
                    %% io:format("Calling:~p~n",[{Mod,Name,Args}]),
 
610
                    apply(Mod, Name, Args);
 
611
                error ->
 
612
                    io:format("Script does not export ~w/~w\n", [Name,Arity]),
 
613
                    my_halt(127)
 
614
            end
 
615
    end.
 
616
 
 
617
format_exception(Class, Reason) ->
 
618
    PF = fun(Term, I) -> 
 
619
                 io_lib:format("~." ++ integer_to_list(I) ++ "P", [Term, 50]) 
 
620
         end,
 
621
    StackTrace = erlang:get_stacktrace(),
 
622
    StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end,
 
623
    lib:format_exception(1, Class, Reason, StackTrace, StackFun, PF).
 
624
 
 
625
fatal(Str) ->
 
626
    throw(Str).
 
627
                                
401
628
my_halt(Reason) ->
402
629
    case process_info(group_leader(), status) of
403
 
        {_,waiting} ->
404
 
            %% Now all output data is down in the driver.
405
 
            %% Give the driver some extra time before halting.
406
 
            receive after 1 -> ok end,
407
 
            halt(Reason);
408
 
        _ ->
409
 
            %% Probably still processing I/O requests.
410
 
            erlang:yield(),
411
 
            my_halt(Reason)
 
630
        {_,waiting} ->
 
631
            %% Now all output data is down in the driver.
 
632
            %% Give the driver some extra time before halting.
 
633
            receive after 1 -> ok end,
 
634
            halt(Reason);
 
635
        _ ->
 
636
            %% Probably still processing I/O requests.
 
637
            erlang:yield(),
 
638
            my_halt(Reason)
 
639
    end.
 
640
 
 
641
hidden_apply(App, M, F, Args) ->
 
642
    try
 
643
        apply(fun() -> M end(), F, Args)
 
644
    catch
 
645
        error:undef ->
 
646
            case erlang:get_stacktrace() of
 
647
                [{M,F,Args} | _] ->
 
648
                    Arity = length(Args),
 
649
                    Text = io_lib:format("Call to ~w:~w/~w in application ~w failed.\n",
 
650
                                         [M, F, Arity, App]),
 
651
                    fatal(Text);                    
 
652
                Stk ->
 
653
                    erlang:raise(error, undef, Stk)
 
654
            end
412
655
    end.