~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/edoc/src/edoc_run.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% =====================================================================
 
2
%% This library is free software; you can redistribute it and/or modify
 
3
%% it under the terms of the GNU Lesser General Public License as
 
4
%% published by the Free Software Foundation; either version 2 of the
 
5
%% License, or (at your option) any later version.
 
6
%%
 
7
%% This library is distributed in the hope that it will be useful, but
 
8
%% WITHOUT ANY WARRANTY; without even the implied warranty of
 
9
%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
 
10
%% Lesser General Public License for more details.
 
11
%%
 
12
%% You should have received a copy of the GNU Lesser General Public
 
13
%% License along with this library; if not, write to the Free Software
 
14
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
 
15
%% USA
 
16
%%
 
17
%% $Id$
 
18
%%
 
19
%% @copyright 2003 Richard Carlsson
 
20
%% @author Richard Carlsson <richardc@csd.uu.se>
 
21
%% @see edoc
 
22
%% @end 
 
23
%% =====================================================================
 
24
 
 
25
%% @doc Interface for calling EDoc from Erlang startup options.
 
26
%%
 
27
%% The following is an example of typical usage in a Makefile:
 
28
%% ```docs:
 
29
%%            erl -noshell -run edoc_run application "'$(APP_NAME)'" \
 
30
%%              '"."' '[{def,{vsn,"$(VSN)"}}]'
 
31
%% '''
 
32
%% (note the single-quotes to avoid shell expansion, and the
 
33
%% double-quotes enclosing the strings).
 
34
%%
 
35
%% <strong>New feature in version 0.6.9</strong>: It is no longer
 
36
%% necessary to write `-s init stop' last on the command line in order
 
37
%% to make the execution terminate. The termination (signalling success
 
38
%% or failure to the operating system) is now built into these
 
39
%% functions.
 
40
 
 
41
-module(edoc_run).
 
42
 
 
43
-export([file/1, application/1, packages/1, files/1, toc/1]).
 
44
 
 
45
-import(edoc_report, [report/2, error/1]).
 
46
 
 
47
 
 
48
%% @spec application([string()]) -> none()
 
49
%%
 
50
%% @doc Calls {@link edoc:application/3} with the corresponding
 
51
%% arguments. The strings in the list are parsed as Erlang constant
 
52
%% terms. The list can be either `[App]', `[App, Options]' or `[App,
 
53
%% Dir, Options]'. In the first case {@link edoc:application/1} is
 
54
%% called instead; in the second case, {@link edoc:application/2} is
 
55
%% called.
 
56
%%
 
57
%% The function call never returns; instead, the emulator is
 
58
%% automatically terminated when the call has completed, signalling
 
59
%% success or failure to the operating system.
 
60
 
 
61
application(Args) ->
 
62
    F = fun () ->
 
63
                case parse_args(Args) of
 
64
                    [App] -> edoc:application(App);
 
65
                    [App, Opts] -> edoc:application(App, Opts);
 
66
                    [App, Dir, Opts] -> edoc:application(App, Dir, Opts);
 
67
                    _ ->
 
68
                        invalid_args("edoc_run:application/1", Args)
 
69
                end
 
70
        end,
 
71
    run(F).
 
72
 
 
73
%% @spec files([string()]) -> none()
 
74
%%
 
75
%% @doc Calls {@link edoc:files/2} with the corresponding arguments. The
 
76
%% strings in the list are parsed as Erlang constant terms. The list can
 
77
%% be either `[Files]' or `[Files, Options]'. In the first case, {@link
 
78
%% edoc:files/1} is called instead.
 
79
%%
 
80
%% The function call never returns; instead, the emulator is
 
81
%% automatically terminated when the call has completed, signalling
 
82
%% success or failure to the operating system.
 
83
 
 
84
files(Args) ->
 
85
    F = fun () ->
 
86
                case parse_args(Args) of
 
87
                    [Files] -> edoc:files(Files);
 
88
                    [Files, Opts] -> edoc:files(Files, Opts);
 
89
                    _ ->
 
90
                        invalid_args("edoc_run:files/1", Args)
 
91
                end
 
92
        end,
 
93
    run(F).
 
94
 
 
95
%% @spec packages([string()]) -> none()
 
96
%%
 
97
%% @doc Calls {@link edoc:application/2} with the corresponding
 
98
%% arguments. The strings in the list are parsed as Erlang constant
 
99
%% terms. The list can be either `[Packages]' or `[Packages, Options]'.
 
100
%% In the first case {@link edoc:application/1} is called instead.
 
101
%%
 
102
%% The function call never returns; instead, the emulator is
 
103
%% automatically terminated when the call has completed, signalling
 
104
%% success or failure to the operating system.
 
105
 
 
106
packages(Args) ->
 
107
    F = fun () ->
 
108
                case parse_args(Args) of
 
109
                    [Packages] -> edoc:packages(Packages);
 
110
                    [Packages, Opts] -> edoc:packages(Packages, Opts);
 
111
                    _ ->
 
112
                        invalid_args("edoc_run:packages/1", Args)
 
113
                end
 
114
        end,
 
115
    run(F).
 
116
 
 
117
%% @hidden   Not official yet
 
118
toc(Args) ->
 
119
    F = fun () ->
 
120
                case parse_args(Args) of
 
121
                    [Dir, Paths] -> edoc:toc(Dir,Paths);
 
122
                    [Dir, Paths, Opts] -> edoc:toc(Dir,Paths,Opts);
 
123
                    _ ->
 
124
                        invalid_args("edoc_run:toc/1", Args)
 
125
                end
 
126
        end,
 
127
    run(F).
 
128
 
 
129
 
 
130
%% @spec file([string()]) -> none()
 
131
%%
 
132
%% @deprecated This is part of the old interface to EDoc and is mainly
 
133
%% kept for backwards compatibility. The preferred way of generating
 
134
%% documentation is through one of the functions {@link application/1},
 
135
%% {@link packages/1} and {@link files/1}.
 
136
%%
 
137
%% @doc Calls {@link edoc:file/2} with the corresponding arguments. The
 
138
%% strings in the list are parsed as Erlang constant terms. The list can
 
139
%% be either `[File]' or `[File, Options]'. In the first case, an empty
 
140
%% list of options is passed to {@link edoc:file/2}.
 
141
%%
 
142
%% The following is an example of typical usage in a Makefile:
 
143
%% ```$(DOCDIR)/%.html:%.erl
 
144
%%            erl -noshell -run edoc_run file '"$<"' '[{dir,"$(DOCDIR)"}]' \
 
145
%%              -s init stop'''
 
146
%%
 
147
%% The function call never returns; instead, the emulator is
 
148
%% automatically terminated when the call has completed, signalling
 
149
%% success or failure to the operating system.
 
150
 
 
151
file(Args) ->
 
152
    F = fun () ->
 
153
                case parse_args(Args) of
 
154
                    [File] -> edoc:file(File, []);
 
155
                    [File, Opts] -> edoc:file(File, Opts);
 
156
                    _ ->
 
157
                        invalid_args("edoc_run:file/1", Args)
 
158
                end
 
159
        end,
 
160
    run(F).
 
161
 
 
162
invalid_args(Where, Args) ->
 
163
    report("invalid arguments to ~s: ~w.", [Where, Args]),
 
164
    shutdown(error).
 
165
 
 
166
run(F) ->
 
167
    wait_init(),
 
168
    case catch {ok, F()} of
 
169
        {ok, _} ->
 
170
            shutdown(ok);
 
171
        {'EXIT', E} ->
 
172
            report("edoc terminated abnormally: ~P.", [E, 10]),
 
173
            shutdown(error);
 
174
        Thrown ->
 
175
            report("internal error: throw without catch in edoc: ~P.",
 
176
                   [Thrown, 15]),
 
177
            shutdown(error)
 
178
    end.
 
179
 
 
180
wait_init() ->
 
181
    case erlang:whereis(code_server) of
 
182
        undefined ->
 
183
            erlang:yield(),
 
184
            wait_init();
 
185
        _ ->
 
186
            ok
 
187
    end.
 
188
 
 
189
%% When and if a function init:stop/1 becomes generally available, we
 
190
%% can use that instead of delay-and-pray when there is an error.
 
191
 
 
192
shutdown(ok) ->
 
193
    %% shut down emulator nicely, signalling "normal termination"
 
194
    init:stop();
 
195
shutdown(error) ->
 
196
    %% delay 1 second to allow I/O to finish
 
197
    receive after 1000 -> ok end,
 
198
    %% stop emulator the hard way with a nonzero exit value
 
199
    halt(1).
 
200
 
 
201
parse_args([A | As]) when atom(A) ->
 
202
    [parse_arg(atom_to_list(A)) | parse_args(As)];
 
203
parse_args([A | As]) ->
 
204
    [parse_arg(A) | parse_args(As)];
 
205
parse_args([]) ->
 
206
    [].
 
207
 
 
208
parse_arg(A) ->
 
209
    case catch {ok, edoc_lib:parse_expr(A, 1)} of
 
210
        {ok, Expr} ->
 
211
            case catch erl_parse:normalise(Expr) of
 
212
                {'EXIT', _} ->
 
213
                    report("bad argument: '~s':", [A]),
 
214
                    exit(error);
 
215
                Term ->
 
216
                    Term
 
217
            end;
 
218
        {error, _, D} ->
 
219
            report("error parsing argument '~s'", [A]),
 
220
            error(D),
 
221
            exit(error)
 
222
    end.