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

« back to all changes in this revision

Viewing changes to lib/erl_docgen/priv/bin/xml_from_edoc.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
%% File    : xml_from_edoc.escript
 
21
%%
 
22
%% Created : 12 Dec 2009 by Lars Thorsen 
 
23
%%----------------------------------------------------------------------
 
24
 
 
25
 
 
26
%%======================================================================
 
27
%% Records 
 
28
%%======================================================================
 
29
-record(args, {suffix=".xml",
 
30
               layout=docb_edoc_xml_cb,
 
31
               def=[],
 
32
               includes=[],
 
33
               preprocess=false,
 
34
               sort_functions=true}).
 
35
 
 
36
 
 
37
%%======================================================================
 
38
%% External functions
 
39
%%======================================================================
 
40
%%----------------------------------------------------------------------
 
41
%% Function: main/1
 
42
%% Description:
 
43
%%----------------------------------------------------------------------
 
44
main(RawOpts) ->
 
45
    case catch parse(RawOpts, erlref, #args{}) of
 
46
        {ok, File, Type, Args} ->
 
47
            case Type of
 
48
                erlref ->
 
49
                    module(File, Args);
 
50
                chapter ->
 
51
                    users_guide(File, Args) 
 
52
            end;
 
53
        {error, Msg} ->
 
54
            io:format("~p\n", [Msg]),
 
55
            usage()
 
56
    end;
 
57
main(_) ->
 
58
    usage().
 
59
        
 
60
%%======================================================================
 
61
%% Internal functions
 
62
%%======================================================================
 
63
 
 
64
%%----------------------------------------------------------------------
 
65
%% Function: usage/0
 
66
%% Description:
 
67
%%----------------------------------------------------------------------
 
68
usage() ->
 
69
    io:format("usage:  xml_from_edoc.escript [<options>] <file> \n"),
 
70
    halt(1).
 
71
 
 
72
 
 
73
%%----------------------------------------------------------------------
 
74
%% Function: module/2
 
75
%% Description:
 
76
%%----------------------------------------------------------------------
 
77
module(File, Args) ->
 
78
    case filelib:is_regular(File) of
 
79
        true ->
 
80
            Opts = [{def,         Args#args.def},
 
81
                    {includes,    Args#args.includes},
 
82
                    {preprocess,  Args#args.preprocess},
 
83
                    {sort_functions, Args#args.sort_functions},
 
84
                    
 
85
                    {app_default, "OTPROOT"},
 
86
                    {file_suffix, Args#args.suffix},
 
87
                    {dir,         "."},
 
88
                    {layout,      Args#args.layout}],
 
89
            edoc:file(File, Opts);
 
90
        false ->
 
91
            io:format("~s: not a regular file\n", [File]),
 
92
            usage()
 
93
    end.
 
94
 
 
95
 
 
96
%%----------------------------------------------------------------------
 
97
%% Function: users_guide/2
 
98
%% Description:
 
99
%%----------------------------------------------------------------------
 
100
users_guide(File, Args) ->
 
101
    case filelib:is_regular(File) of
 
102
        true ->
 
103
            Opts = [{def,         Args#args.def},
 
104
                    {app_default, "OTPROOT"},
 
105
                    {file_suffix, Args#args.suffix},
 
106
                    {layout,      Args#args.layout}],
 
107
            
 
108
            Env = edoc_lib:get_doc_env(Opts),
 
109
            
 
110
            {ok, Tags} =
 
111
                edoc_extract:file(File, overview, Env, Opts),
 
112
            Data =
 
113
                edoc_data:overview("Overview", Tags, Env, Opts),
 
114
            F = fun(M) -> M:overview(Data, Opts) end,
 
115
            Text = edoc_lib:run_layout(F, Opts),
 
116
            
 
117
            OutFile = "chapter" ++ Args#args.suffix,
 
118
            edoc_lib:write_file(Text, ".", OutFile);
 
119
        false ->
 
120
            io:format("~s: not a regular file\n", [File]),
 
121
            usage()
 
122
    end.
 
123
 
 
124
 
 
125
 
 
126
parse(["-xml" |RawOpts], Type, Args) ->
 
127
    parse(RawOpts, Type, Args); % default, no update of record necessary
 
128
parse(["-sgml" |RawOpts], Type, Args) ->
 
129
    parse(RawOpts, Type, Args#args{suffix=".sgml", layout=docb_edoc_sgml_cb});
 
130
parse(["-chapter" |RawOpts], _Type, Args) ->
 
131
    parse(RawOpts, chapter, Args);
 
132
parse(["-def", Key, Val |RawOpts], Type, Args) ->
 
133
    Args2 = Args#args{def=Args#args.def++[{list_to_atom(Key), Val}]},
 
134
    parse(RawOpts, Type, Args2);
 
135
 
 
136
parse(["-i", Dir |RawOpts], Type, Args) ->
 
137
    Args2 = Args#args{includes=Args#args.includes++[Dir]},
 
138
    parse(RawOpts, Type, Args2);
 
139
parse(["-preprocess", Bool |RawOpts], Type, Args) when Bool == "true";
 
140
                                                       Bool == "false" ->
 
141
    parse(RawOpts, Type, Args#args{preprocess=list_to_atom(Bool)});
 
142
parse(["-sort_functions", Bool |RawOpts], Type, Args) when Bool == "true";
 
143
                                                           Bool == "false" ->
 
144
    parse(RawOpts, Type, Args#args{sort_functions=list_to_atom(Bool)});
 
145
parse([File], Type, Args) ->
 
146
    {ok, File, Type, Args};
 
147
parse([Opt | _RawOpts], _Type, _Args) ->
 
148
    {error, io_lib:format("Bad option: ~p", [Opt])}.
 
149