~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/docbuilder/src/docb_tr_part2html.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

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 expressed 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 1999-2000, Ericsson 
14
 
%% Utvecklings AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
17
 
%%
18
 
-module(docb_tr_part2html).
19
 
 
20
 
-export([extension/0, transform/3, rule/2, rule/3]).
21
 
 
22
 
extension() ->
23
 
    ".html".
24
 
 
25
 
transform(File, {part, _Attrs, [Header| Rest]}, Opts0) ->
26
 
 
27
 
    %% Extract header data
28
 
    Title = docb_html_util:extract_header_data(title, Header),
29
 
 
30
 
    %% Create the framing HTML document
31
 
    OutFile = docb_util:outfile(File ++ "_frame", ".html", Opts0),
32
 
    case file:open(OutFile, [write]) of
33
 
        {ok, Frame} ->
34
 
            io:format(Frame,
35
 
"<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Frameset//EN\"
36
 
   \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-frameset.dtd\">
37
 
<!-- This document was generated using DocBuilder-" ++ docb_util:version() ++ " -->
38
 
<html xmlns=\"http://www.w3.org/1999/xhtml\" xml:lang=\"en\" lang=\"en\">
39
 
<head>
40
 
  <title>~s</title>
41
 
  " ++ docb_util:html_snippet(head,  Opts0) ++ "
42
 
</head>
43
 
<frameset cols=\"200, *\">
44
 
  <frame src=\"~s\" name=\"toc\"/>
45
 
  <frame src=\"~s\" name=\"document\"/>
46
 
  <noframes>
47
 
    <body bgcolor=\"#FFFFFF\" text=\"#000000\" link=\"#0000FF\"
48
 
          vlink=\"#FF00FF\" alink=\"#FF0000\">
49
 
    <p>This documentation requires a browser that can handle frames</p>
50
 
    </body>
51
 
  </noframes>
52
 
</frameset>
53
 
</html>
54
 
",
55
 
                      [Title, File ++ ".html", File ++ "_first.html"]),
56
 
            file:close(Frame)
57
 
    end,
58
 
 
59
 
    %% Create the front HTML document
60
 
    docb_main:transform(first, html, Opts0, File ++ "_first",
61
 
                        {first, [], [Header| Rest]}),
62
 
 
63
 
    %% Extract files to include
64
 
    Files =
65
 
        case Rest of
66
 
            [{description, _, _}| NewRest] ->
67
 
                lists:map(fun({include, [{_, _, F}], _}) -> filename:rootname(F) end,
68
 
                          NewRest);
69
 
            [{include, _, _}| _NewRest] ->
70
 
                lists:map(fun({include, [{_, _, F}], _}) -> filename:rootname(F) end, Rest)
71
 
        end,
72
 
 
73
 
    %% Concat all chapters into a *big* parse tree
74
 
    %% Also transform them to HTML
75
 
    TransformP = not docb_util:an_option(framework_only, Opts0),
76
 
    TOpts = [dict, {part_application,File}],
77
 
    ConcatTree = concat_files(Files, Opts0, TransformP, TOpts),
78
 
 
79
 
    %% Create a cites dictionary
80
 
    docb_main:transform(cite, html, Opts0, File ++ "_cite",
81
 
                        {cite, [], [Header| ConcatTree]}),
82
 
 
83
 
    %% Create a terms dictionary
84
 
    docb_main:transform(term, html, Opts0, File ++ "_term",
85
 
                        {term, [], [Header| ConcatTree]}),
86
 
 
87
 
    %% Find all fascicules to be put in the top menu of the table of
88
 
    %% contents
89
 
    Ext = docb_util:lookup_option(src_type, Opts0),
90
 
    Opts2 =
91
 
        case filelib:is_regular("fascicules"++Ext) of
92
 
            true ->
93
 
                case docb_main:parse1("fascicules", Opts0) of
94
 
                    {ok, Parse} ->
95
 
                        FascData = get_fasc_data(Parse),
96
 
                        case lists:keyfind(File, 1, FascData) of
97
 
                            {_, _, "YES", _} ->
98
 
                                OrigFile =
99
 
                                    docb_util:outfile(File++"_frame",
100
 
                                                      ".html", Opts0),
101
 
                                EntryFile =
102
 
                                    docb_util:outfile("index",
103
 
                                                      ".html", Opts0),
104
 
                                docb_util:message(info,
105
 
                                                  "Copying ~s to ~s",
106
 
                                                  [OrigFile,EntryFile]),
107
 
                                file:copy(OrigFile, EntryFile);
108
 
                            _ ->
109
 
                                ok
110
 
                        end,
111
 
                        [{fascdata, FascData}| Opts0];
112
 
                    errors ->
113
 
                        %% do not bother
114
 
                        docb_util:message(
115
 
                          warning,
116
 
                          "fascicules~s could not be parsed,"
117
 
                          " no index.html created~n", [Ext]),
118
 
                        Opts0
119
 
                end;
120
 
            _ ->
121
 
                %% do not bother
122
 
                docb_util:message(warning,
123
 
                                  "fascicules~s not found, "
124
 
                                  "no index.html created~n",
125
 
                                  [Ext]),
126
 
                Opts0
127
 
        end,
128
 
 
129
 
    %% Create ToC parse tree
130
 
    {{toc, [{"FILE", "CDATA", File}], [Header| ConcatTree]}, Opts2}.
131
 
 
132
 
concat_files(Files, Opts, TransformP, TOpts) ->
133
 
    Ext = docb_util:lookup_option(src_type, Opts),
134
 
    concat_files(Files, [], 1, Opts, TransformP, TOpts, Ext).
135
 
 
136
 
concat_files([File | Rest], Body, ChLevel, Opts, TP, TOpts, Ext) ->
137
 
    case docb_main:parse1(File, Opts) of
138
 
        {ok, Parse} ->
139
 
            {TopTag, Attrs, [Header = {header, _, HeaderContents} | More]} = Parse,
140
 
            {title,_,Title} = lists:keyfind(title,1,HeaderContents),
141
 
            NewMore = [{section, [], [{title, [], Title}| More]}],
142
 
            NewParse = {TopTag, Attrs, [Header| NewMore]},
143
 
            if
144
 
                TP ->
145
 
                    docb_util:message(info,
146
 
                                      "Processing \"~s~s\"",
147
 
                                      [File, Ext]),
148
 
                    Opts2 =
149
 
                        [html, {number,integer_to_list(ChLevel)}] ++
150
 
                        TOpts ++ Opts,
151
 
                    docb_main:transform(TopTag, html, Opts2, File,
152
 
                                        NewParse);
153
 
                true -> ignore
154
 
            end,
155
 
            NumberTree =
156
 
                docb_html_util:number(NewParse,
157
 
                                      integer_to_list(ChLevel), File),
158
 
            {_, [], [_| NewBody]} = NumberTree,
159
 
            Body ++ concat_files(Rest, NewBody, ChLevel+1, Opts,
160
 
                                 TP, TOpts, Ext);
161
 
        errors ->
162
 
            throw({error,"Parse error when building chapter "++File})
163
 
    end;
164
 
concat_files([], Body, _ChLevel, _Opts, _TP, _TOpts, _Ext) ->
165
 
    Body.
166
 
 
167
 
rule([section| _], _) ->
168
 
    {"", ""};
169
 
 
170
 
rule(_, _) ->
171
 
    {drop, ""}.
172
 
 
173
 
rule([toc| _], {_Depth, [File], [Header| _]}, Opts) ->
174
 
    case docb_util:lookup_option(fascdata, Opts) of
175
 
        false ->
176
 
            {{docb_html_layout:part_toc_top(
177
 
                docb_html_util:all_header_data(Header), File, Opts),
178
 
              docb_html_layout:part_toc_bot()}, Opts};
179
 
        FascData ->
180
 
            HRefTexts =
181
 
                lists:map(
182
 
                  fun({_File, HRef, _Entry, PCText}) ->
183
 
                          {HRef, docb_html_util:pcdata_to_html(PCText)}
184
 
                  end,
185
 
                  FascData),
186
 
            {{docb_html_layout:part_toc_top(
187
 
                docb_html_util:all_header_data(Header),
188
 
                File, Opts, HRefTexts),
189
 
             docb_html_layout:part_toc_bot()}, Opts}
190
 
    end;
191
 
 
192
 
rule([title| Rest], {_, [Number, File], [{pcdata, _, Title}]}, Opts) ->
193
 
    N = docb_html_util:count_sections(Rest),
194
 
    OutFile = docb_html_util:make_anchor_href(File),
195
 
    if
196
 
        N == 1 ->
197
 
            {{drop,
198
 
              "<hr/>\n<small>" ++
199
 
              Number ++
200
 
              " <a target=\"document\" href=\"" ++ OutFile ++ "#" ++
201
 
              Number ++ "\">" ++
202
 
              docb_html_util:pcdata_to_html(Title) ++
203
 
              "</a></small><br/>\n"},
204
 
             Opts};
205
 
        N < 3 ->
206
 
            {{drop,
207
 
              "<small>" ++
208
 
              Number ++
209
 
              " <a target=\"document\" href=\"" ++ OutFile ++ "#" ++
210
 
              Number ++ "\">" ++
211
 
              docb_html_util:pcdata_to_html(Title) ++
212
 
              "</a></small><br/>\n"},
213
 
             Opts};
214
 
        true ->
215
 
            {{drop, ""}, Opts}
216
 
    end.
217
 
 
218
 
%% Parsed fascicules:
219
 
%%   {fascicules,[],
220
 
%%    [{fascicule, [{"FILE","CDATA","refman"},
221
 
%%                  {"HREF","CDATA","refman_frame.html"},
222
 
%%                  {"ENTRY","TOKEN","YES"}],
223
 
%%                 [{pcdata, [], ""    Reference  Manual\\n  \n"}]},
224
 
%% Returns: [{File, HRef, Entry, Text}].
225
 
get_fasc_data({fascicules, _, Fascs}) ->
226
 
    lists:map(
227
 
      fun({fascicule, Atts, Trees}) -> 
228
 
              AVals = get_avals(Atts),
229
 
              PCText = get_pc_text(Trees),
230
 
              list_to_tuple(lists:append([AVals, [PCText]])) end,
231
 
      Fascs).
232
 
 
233
 
get_avals(Atts) ->
234
 
    [element(3, Tuple) || Tuple <- Atts].
235
 
 
236
 
get_pc_text([{pcdata, _, Text}]) ->
237
 
    Text.