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

« back to all changes in this revision

Viewing changes to erts/boot/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,
2
 
%% Version 1.1, (the "License"); you may not use this file except in
3
 
%% compliance with the License. You should have received a copy of the
4
 
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
7
 
%% Software distributed under the License is distributed on an "AS IS"
8
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
 
%% the License for the specific language governing rights and limitations
10
 
%% under the License.
11
 
%% 
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
 
%%
18
 
-module(escript).
19
 
 
20
 
-export([start/1, interpret/1]).
21
 
 
22
 
-import(lists, [foldl/3, map/2, member/2, reverse/1]).
23
 
 
24
 
start([_|X]) ->
25
 
    X0 = map(fun(I) -> binary_to_list(I) end, X),
26
 
    %% io:format("Escript:~p~n",[X0]),
27
 
    [_,File|Args] = X0,
28
 
    %% io:format("File=~s~n",[File]),
29
 
    {Nerrs, Parse, Mode} = parse_file(File),
30
 
    if
31
 
        Nerrs > 0 ->
32
 
            io:format("Script terminated~n"),
33
 
            erlang:halt();
34
 
        true ->
35
 
            case Mode of
36
 
                interpret ->
37
 
                    interpret(File, Parse, Args);
38
 
                compile ->
39
 
                    compile(Parse, Args)
40
 
            end
41
 
    end.
42
 
 
43
 
interpret([AFile]) ->
44
 
    File = atom_to_list(AFile),
45
 
    {Nerrs, Parse, Mode} = parse_include_file(File, 0, [], interpret),
46
 
    Args = [],
47
 
    if
48
 
        Nerrs > 0 ->
49
 
            io:format("Script terminated~n"),
50
 
            erlang:halt();
51
 
        true ->
52
 
            case Mode of
53
 
                interpret ->
54
 
                    interpret(File, Parse, Args);
55
 
                compile ->
56
 
                    compile(Parse, Args)
57
 
            end
58
 
    end.
59
 
 
60
 
interpret(File, Parse, Args) ->
61
 
    Dict  = parse_to_dict(Parse),
62
 
    ArgsA = erl_parse:abstract(Args, 999),
63
 
    Call = {call,999,{atom,999,main},[ArgsA]},
64
 
    erl_eval:expr(Call,
65
 
                  erl_eval:new_bindings(),
66
 
                  {value, fun(I, J) ->
67
 
                                  code_handler(I, J, Dict, File)
68
 
                          end}),
69
 
    erlang:halt().
70
 
 
71
 
 
72
 
compile(Parse, Args) ->
73
 
    Mod = mk_mod(),
74
 
    case compile:forms([Mod|Parse]) of
75
 
        {ok, Module, BeamCode} -> 
76
 
            erlang:load_module(Module, BeamCode),
77
 
            apply(Module, main, [Args]),
78
 
            erlang:halt();
79
 
        O ->
80
 
            io:format("Compiler errors~n"),
81
 
            erlang:halt()
82
 
    end.
83
 
 
84
 
 
85
 
parse_to_dict(L) -> parse_to_dict(L, dict:new()).
86
 
 
87
 
parse_to_dict([{function,_,Name,Arity,Clauses}|T], Dict0) ->
88
 
    Dict = dict:store({local, Name,Arity}, Clauses, Dict0),
89
 
    parse_to_dict(T, Dict);
90
 
parse_to_dict([{attribute,_,import,{Mod,Funcs}}|T], Dict0) ->
91
 
    Dict = foldl(fun(I, D) ->
92
 
                         dict:store({remote,I}, Mod, D)
93
 
                 end, Dict0, Funcs),
94
 
    parse_to_dict(T, Dict);
95
 
parse_to_dict([_|T], Dict) ->
96
 
    parse_to_dict(T, Dict);
97
 
parse_to_dict([], Dict) ->
98
 
    Dict.
99
 
 
100
 
%% make a temporary module name
101
 
 
102
 
mk_mod() ->
103
 
    {I,J,K} = erlang:now(),
104
 
    Mod = list_to_atom("tmp" ++ integer_to_list(I) ++ integer_to_list(J) ++
105
 
                       integer_to_list(K)),
106
 
    {attribute,999,module, Mod}.
107
 
 
108
 
parse_file(File) ->
109
 
    {Nerrs, L, Mode} = parse_file(File, 0, [], interpret),
110
 
    {Nerrs, reverse(L), Mode}.
111
 
 
112
 
parse_file(File, Nerrs, L, Mode) ->
113
 
    {ok, P} = file:open(File, read),
114
 
    %% This is to skip the first line in the script
115
 
    io:get_line(P, ''),
116
 
    Ret = parse_loop(P, File, io:parse_erl_form(P, '', 2), Nerrs, L, Mode),
117
 
    file:close(P),
118
 
    Ret.
119
 
 
120
 
parse_include_file(File, Nerrs, L, Mode) ->
121
 
    {ok, P} = file:open(File, read),
122
 
    Ret = parse_loop(P, File, io:parse_erl_form(P, '', 1), Nerrs, L, Mode),
123
 
    file:close(P),
124
 
    Ret.
125
 
 
126
 
parse_loop(P, _, {eof,_}, Nerrs, L, Mode) ->
127
 
    {Nerrs, L, Mode};
128
 
parse_loop(P, File, {ok, Form, Ln}, Nerrs, L0, Mode) ->
129
 
    case Form of
130
 
        {attribute,_,mode,compile} ->
131
 
            parse_loop(P,File,io:parse_erl_form(P,'',Ln),Nerrs,L0,compile);
132
 
        {attribute,_,include,Include} ->
133
 
            {Nerrs1, L1, Mode1} = parse_include_file(Include, Nerrs, L0, Mode),
134
 
            parse_loop(P,File,io:parse_erl_form(P,'',Ln),Nerrs1,L1,Mode1);
135
 
        Form ->
136
 
            parse_loop(P,File,io:parse_erl_form(P,'',Ln),Nerrs,[Form|L0],Mode)
137
 
    end;
138
 
parse_loop(P, File, {error,{Ln,Mod,Args}, Ln1}, Nerrs, L, Mode) ->
139
 
    io:format("Error in File:~s Line:~w ~s~n",
140
 
              [File, Ln, Mod:format_error(Args)]),
141
 
    parse_loop(P, File, io:parse_erl_form(P, '', Ln1), Nerrs+1, L, Mode);
142
 
parse_loop(P, _, X, Nerrs, L, Mode) ->
143
 
    io:format("Unexpected form:~p~n",[X]),
144
 
    {Nerrs+1, L, Mode}.
145
 
    
146
 
code_handler(local, [file], _, File) ->
147
 
    File;
148
 
code_handler(Name, Args, Dict, File) ->
149
 
    %% io:format("code handler=~p~n",[{Name, Args}]),
150
 
    Arity = length(Args),
151
 
    case dict:find({local,Name,Arity}, Dict) of
152
 
        {ok, Cs} ->
153
 
            LF = {value, fun(I, J) ->
154
 
                                 code_handler(I, J, Dict, File)
155
 
                         end},
156
 
            case erl_eval:match_clause(Cs, Args,erl_eval:new_bindings(),LF) of
157
 
                {Body, Bs} ->
158
 
                    {value, Val, Bs1} = erl_eval:exprs(Body, Bs, LF),
159
 
                    Val;
160
 
                nomatch ->
161
 
                    io:format("escript: Fatal error"),
162
 
                    erlang:halt(-1)
163
 
            end;
164
 
        error ->
165
 
            case dict:find({remote,{Name,Arity}}, Dict) of
166
 
                {ok, Mod} ->
167
 
                    %% io:format("Calling:~p~n",[{Mod,Name,Args}]),
168
 
                    apply(Mod, Name, Args);
169
 
                error ->
170
 
                    io:format("Script does not export ~w/~w~n",
171
 
                              [Name,Arity]),
172
 
                    erlang:halt()
173
 
            end
174
 
    end.
175
 
 
176
 
 
177
 
        
178
 
 
179
 
 
180
 
    
181
 
 
182
 
 
183