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

« back to all changes in this revision

Viewing changes to lib/erl_docgen/priv/bin/specs_gen.escript

  • 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
#!/usr/bin/env escript
 
2
%% -*- erlang -*-
 
3
%% %CopyrightBegin%
 
4
%%
 
5
%% Copyright Ericsson AB 2010. All Rights Reserved.
 
6
%%
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%%
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%%
 
18
%% %CopyrightEnd%
 
19
 
 
20
%%% <script> [-I<dir>]... [-o<dir>] [-module Module] [File]
 
21
%%%
 
22
%%% Use EDoc and the layout module 'otp_specs' to create an XML file
 
23
%%% containing Dialyzer types and specifications (-type, -spec).
 
24
%%%
 
25
%%% Options:
 
26
%%%
 
27
%%%  "-o<dir>" The output directory for the created file.
 
28
%%%            Default is ".".
 
29
%%%  "-I<dir>" Directory to be searched when including a file.
 
30
%%%  "-module Module"
 
31
%%%            Module name to use when there is no File argument.
 
32
%%%            A temporary file will be created.
 
33
%%%            Exactly one of -module Module and File must be given.
 
34
%%%
 
35
%%% The name of the generated file is "specs_<module>.xml". Its exact
 
36
%%% format is not further described here.
 
37
 
 
38
main(Args) ->
 
39
    case catch parse(Args, [], ".", no_module) of
 
40
        {ok, FileSpec, InclFs, Dir} ->
 
41
            call_edoc(FileSpec, InclFs, Dir);
 
42
        {error, Msg} ->
 
43
            io:format("~s\n", [Msg]),
 
44
            usage()
 
45
    end.
 
46
 
 
47
parse(["-o"++Dir | Opts], InclFs, _, Module) ->
 
48
    parse(Opts, InclFs, Dir, Module);
 
49
parse(["-I"++I | Opts], InclFs, Dir, Module) ->
 
50
    parse(Opts, [I | InclFs], Dir, Module);
 
51
parse(["-module", Module | Opts], InclFs, Dir, _) ->
 
52
    parse(Opts, InclFs, Dir, Module);
 
53
parse([File], InclFs, Dir, no_module) ->
 
54
    {ok, {file, File}, lists:reverse(InclFs), Dir};
 
55
parse([_], _, _, _) ->
 
56
    {error, io_lib:format("Cannot have both -module option and file", [])};
 
57
parse([], _, _, no_module) ->
 
58
    {error, io_lib:format("Missing -module option or file", [])};
 
59
parse([], InclFs, Dir, Module) ->
 
60
    {ok, {module, Module}, lists:reverse(InclFs), Dir};
 
61
parse(Args, _, _, _) ->
 
62
    {error, io_lib:format("Bad arguments: ~p", [Args])}.
 
63
 
 
64
usage() ->
 
65
    io:format("usage:  ~s [-I<include_dir>]... [-o<out_dir>] "
 
66
              "[-module <module>] [file]\n", [escript:script_name()]),
 
67
    halt(1).
 
68
 
 
69
call_edoc(FileSpec, InclFs, Dir) ->
 
70
    Incl = [{includes, InclFs}],
 
71
    Pre = [{preprocess, true}],
 
72
    Choice = [{dialyzer_specs, all}],
 
73
    DirOpt = [{dir, Dir}],
 
74
    Pretty = [{pretty_print, erl_pp}],
 
75
    Layout = [{layout, otp_specs},
 
76
              {file_suffix, ".specs"},
 
77
              {stylesheet, ""}],
 
78
    Warn = [{report_missing_type, false},
 
79
            {report_type_mismatch, false}],
 
80
    OptionList = (DirOpt ++ Choice ++ Pre ++ Warn ++ Pretty ++ Layout ++ Incl),
 
81
    {File, TmpFile} = case FileSpec of
 
82
                          {file, File0} ->
 
83
                              {File0, false};
 
84
                          {module, Module} ->
 
85
                              {create_tmp_file(Dir, Module), true}
 
86
                      end,
 
87
    try edoc:files([File], OptionList) of
 
88
        ok ->
 
89
            clean_up(Dir, File, TmpFile),
 
90
            rename(Dir, File)
 
91
    catch
 
92
        _:_ ->
 
93
            io:format("EDoc could not process file '~s'\n", [File]),
 
94
            clean_up(Dir, File, TmpFile),
 
95
            halt(3)
 
96
    end.
 
97
 
 
98
rename(Dir, F) ->
 
99
    Mod = filename:basename(F, ".erl"),
 
100
    Old = filename:join(Dir, Mod ++ ".specs"),
 
101
    New = filename:join(Dir, "specs_" ++ Mod ++ ".xml"),
 
102
    case file:rename(Old, New) of
 
103
        ok ->
 
104
            ok;
 
105
        {error, R} ->
 
106
            R1 = file:format_error(R),
 
107
            io:format("could not rename file '~s': ~s\n", [New, R1]),
 
108
            halt(2)
 
109
    end.
 
110
 
 
111
clean_up(Dir, File, TmpFile) ->
 
112
    [file:delete(File) || TmpFile],
 
113
    _ = [file:delete(filename:join(Dir, F)) ||
 
114
            F <- ["packages-frame.html",
 
115
                  "overview-summary.html",
 
116
                  "modules-frame.html",
 
117
                  "index.html", "erlang.png", "edoc-info"]],
 
118
    ok.
 
119
 
 
120
create_tmp_file(Dir, Module) ->
 
121
    TmpFile = filename:join(Dir, Module++".erl"),
 
122
    case file:write_file(TmpFile, "-module(" ++ Module ++ ").\n") of
 
123
        ok ->
 
124
            TmpFile;
 
125
        {error, R} ->
 
126
            R1 = file:format_error(R),
 
127
            io:format("could not write file '~s': ~s\n", [TmpFile, R1]),
 
128
            halt(2)
 
129
    end.