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

« back to all changes in this revision

Viewing changes to lib/erl_docgen/src/docgen_edoc_xml_cb.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 Licence for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%%
 
12
%% The Initial Developer of the Original Code is Ericsson AB.
 
13
%% Portions created by Ericsson are Copyright 1999-2006, Ericsson AB.
 
14
%% All Rights Reserved.��
 
15
%%
 
16
%%     $Id$
 
17
%%
 
18
-module(docgen_edoc_xml_cb).
 
19
 
 
20
%% This is the EDoc callback module for creating erlref
 
21
%% documents (man pages) in XML format, and also a chapter
 
22
%% document based on "overview.edoc".
 
23
%%
 
24
%% edoc:file(File, [{layout,docgen_edoc_xml_cb},{file_suffix,".xml"},
 
25
%%                  {preprocess,true}]).
 
26
%%
 
27
%% The origin of this file is the edoc module otpsgml_layout.erl
 
28
%% written by Richard Carlsson.
 
29
 
 
30
-export([module/2, overview/2]).
 
31
 
 
32
-include("xmerl.hrl").
 
33
 
 
34
-define(NL, "\n").
 
35
 
 
36
%%-User interface-------------------------------------------------------
 
37
 
 
38
%% ERLREF
 
39
module(Element, Opts) ->
 
40
    SortP = proplists:get_value(sort_functions, Opts, true),
 
41
    XML = layout_module(Element, SortP),
 
42
    xmerl:export_simple([XML], docgen_xmerl_xml_cb, []).
 
43
 
 
44
%% CHAPTER
 
45
overview(Element, _Opts) ->
 
46
    XML = layout_chapter(Element),
 
47
    xmerl:export_simple([XML], docgen_xmerl_xml_cb, []).
 
48
 
 
49
%%--Internal functions--------------------------------------------------
 
50
 
 
51
layout_module(#xmlElement{name = module, content = Es}=E, SortP) ->
 
52
    Name = get_attrval(name, E),
 
53
    Desc = get_content(description, Es),
 
54
    ShortDesc = text_only(get_content(briefDescription, Desc)),
 
55
    FullDesc =  otp_xmlify(get_content(fullDescription, Desc)),
 
56
    Types0 = get_content(typedecls, Es),
 
57
    Types1 = lists:sort([{type_name(Et), Et} || Et <- Types0]),
 
58
    Functions =
 
59
        case SortP of
 
60
            true ->
 
61
                lists:sort([{function_name(Ef), Ef} ||
 
62
                               Ef <- get_content(functions, Es)]);
 
63
            false ->
 
64
                [{function_name(Ef), Ef} ||
 
65
                    Ef <- get_content(functions, Es)]
 
66
        end,
 
67
    Header = {header, [
 
68
                       ?NL,{title, [Name]},
 
69
                       ?NL,{prepared, [""]},
 
70
                       ?NL,{responsible, [""]},
 
71
                       ?NL,{docno, ["1"]},
 
72
                       ?NL,{approved, [""]},
 
73
                       ?NL,{checked, [""]},
 
74
                       ?NL,{date, [""]},
 
75
                       ?NL,{rev, ["A"]},
 
76
                       ?NL,{file, [Name++".xml"]}
 
77
                      ]},
 
78
    Module = {module, [Name]},
 
79
    ModuleSummary = {modulesummary, ShortDesc},
 
80
    Description = {description, [?NL|FullDesc]},
 
81
    Types = case Types1 of
 
82
                [] -> [];
 
83
                _ ->
 
84
                    [?NL, {section,[{title,["DATA TYPES"]},
 
85
                                    {marker,[{id,"types"}],[]},
 
86
                                    ?NL|types(Types1)]}]
 
87
            end,
 
88
    Funcs = functions(Functions),
 
89
    See = seealso_module(Es),
 
90
    Authors = {authors, authors(Es)},
 
91
    {erlref,
 
92
     [?NL,Header,
 
93
      ?NL,Module,
 
94
      ?NL,ModuleSummary,
 
95
      ?NL,Description]
 
96
     ++ Types ++
 
97
     [?NL,Funcs,
 
98
      ?NL,See,
 
99
      ?NL,Authors]
 
100
    }.
 
101
 
 
102
layout_chapter(#xmlElement{name=overview, content=Es}) ->
 
103
    Title = get_text(title, Es),
 
104
    Header = {header, [
 
105
                       ?NL,{title,[Title]},
 
106
                       ?NL,{prepared,[""]},
 
107
                       ?NL,{docno,[""]},
 
108
                       ?NL,{date,[""]},
 
109
                       ?NL,{rev,[""]},
 
110
                       ?NL,{file, ["chapter.xml"]}
 
111
                      ]},
 
112
    DescEs = get_content(description, Es),
 
113
    FullDescEs = get_content(fullDescription, DescEs),
 
114
    Sections = chapter_ify(FullDescEs, first),
 
115
    {chapter, [?NL, Header, ?NL | Sections]}.
 
116
 
 
117
chapter_ify([], _) ->
 
118
    [];
 
119
chapter_ify(Es, first) ->
 
120
    %% Everything up to the first section should be made into
 
121
    %% plain paragraphs -- or if no first section is found, everything
 
122
    %% should be made into one
 
123
    case find_next(h3, Es) of
 
124
        {Es, []} ->
 
125
            SubSections = subchapter_ify(Es, first),
 
126
            [{section, [?NL,{title,["Overview"]},
 
127
                        ?NL | SubSections]}];
 
128
        {FirstEs, RestEs} ->
 
129
            otp_xmlify(FirstEs) ++ chapter_ify(RestEs, next)
 
130
    end;
 
131
chapter_ify([#xmlElement{name=h3} = E | Es], next) ->
 
132
    {SectionEs, RestEs} = find_next(h3, Es),
 
133
    SubSections = subchapter_ify(SectionEs, first),
 
134
    {Marker, Title} = chapter_title(E),
 
135
    [{section, [?NL,{marker,[{id,Marker}],[]},
 
136
                ?NL,{title,[Title]},
 
137
                ?NL | SubSections]} | chapter_ify(RestEs, next)].
 
138
 
 
139
subchapter_ify([], _) ->
 
140
    [];
 
141
subchapter_ify(Es, first) ->
 
142
    %% Everything up to the (possible) first subsection should be
 
143
    %% made into plain paragraphs
 
144
    {FirstEs, RestEs} = find_next(h4, Es),
 
145
    otp_xmlify(FirstEs) ++ subchapter_ify(RestEs, next);
 
146
subchapter_ify([#xmlElement{name=h4} = E | Es], next) ->
 
147
    {SectionEs, RestEs} = find_next(h4, Es),
 
148
    Elements = otp_xmlify(SectionEs),
 
149
    {Marker, Title} = chapter_title(E),
 
150
    [{section, [?NL,{marker,[{id,Marker}],[]},
 
151
                ?NL,{title,[Title]},
 
152
                ?NL | Elements]} | subchapter_ify(RestEs, next)].
 
153
 
 
154
chapter_title(#xmlElement{content=Es}) -> % name = h3 | h4
 
155
    case Es of
 
156
        [#xmlElement{name=a} = E] ->
 
157
            {get_attrval(name, E), get_text(E)}
 
158
    end.
 
159
 
 
160
%%--XHTML->XML transformation-------------------------------------------
 
161
 
 
162
%% otp_xmlify(Es1) -> Es2
 
163
%%   Es1 = Es2 = [#xmlElement{} | #xmlText{}]
 
164
%% Fix things that are allowed in XHTML but not in chapter/erlref DTDs.
 
165
%% 1)  lists (<ul>, <ol>, <dl>) and code snippets (<pre>) can not occur
 
166
%%     within a <p>, such a <p> must be splitted into a sequence of <p>,
 
167
%%     <ul>, <ol>, <dl> and <pre>.
 
168
%% 2)  <a> must only have either a href attribute (corresponds to a
 
169
%%     <seealso> or <url> in the XML code) in which case its content
 
170
%%     must be plain text; or a name attribute (<marker>).
 
171
%% 3a) <b> content must be plain text.
 
172
%%  b) <em> content must be plain text (or actually a <code> element
 
173
%%     as well, but a simplification is used here).
 
174
%%  c) <pre> content must be plain text (or could actually contain
 
175
%%     <input> as well, but a simplification is used here).
 
176
%% 4)  <code> content must be plain text, or the element must be split
 
177
%%     into a list of elements.
 
178
%% 5a) <h1>, <h2> etc is not allowed - replaced by its content within
 
179
%%     a <b> tag.
 
180
%%  b) <center> is not allowed - replaced by its content.
 
181
%%  c) <font>   -"-
 
182
%% 6)  <table> is not allowed in erlref, translated to text instead.
 
183
%%     Also a <table> in chapter without a border is translated to text.
 
184
%%     A <table> in chapter with a border must contain a <tcaption>.
 
185
%% 7)  <sup> is not allowed - is replaced with its text content
 
186
%%     within parenthesis.
 
187
%% 8)  <blockquote> contents may need to be made into paragraphs
 
188
%% 9)  <th> (table header) is not allowed - is replaced by
 
189
%%     <td><em>...</em></td>.
 
190
otp_xmlify([]) ->
 
191
    [];
 
192
otp_xmlify(Es0) ->
 
193
    Es = case is_paragraph(hd(Es0)) of
 
194
 
 
195
             %% If the first element is a <p> xmlElement, then
 
196
             %% the entire element list is ready to be otp_xmlified.
 
197
             true ->
 
198
                 Es0;
 
199
 
 
200
             %% If the first element is not a <p> xmlElement, then all
 
201
             %% elements up to the first <p> (or end of list) must be
 
202
             %% made into a paragraph (using the {p, Es} construction)
 
203
             %% before the list is otp_xmlified.
 
204
             false ->
 
205
                 case find_next(p, Es0, []) of
 
206
                     {[#xmlText{value=Str}] = First, Rest} ->
 
207
                         %% Special case: Making a paragraph out of a
 
208
                         %% blank line isn't a great idea.
 
209
                         case is_empty(Str) of
 
210
                             true ->
 
211
                                 Rest;
 
212
                             false ->
 
213
                                 [{p,First}|Rest]
 
214
                         end;
 
215
                     {First, Rest} ->
 
216
                         [{p,First}|Rest]
 
217
                 end
 
218
         end,
 
219
 
 
220
    %% Fix paragraph breaks not needed in XHTML but in XML
 
221
    EsFixed = otp_xmlify_fix(Es),
 
222
 
 
223
    otp_xmlify_es(EsFixed).
 
224
 
 
225
%% EDoc does not always translate empty lines (with leading "%%")
 
226
%% as paragraph break, this is the fix
 
227
otp_xmlify_fix(Es) ->
 
228
    otp_xmlify_fix(Es, []).
 
229
otp_xmlify_fix([#xmlText{value="\n \n"++_} = E1, E2 | Es], Res) ->
 
230
    %% This is how it looks when generating an erlref from a .erl file
 
231
    case is_paragraph(E2) of
 
232
        false ->
 
233
            {P, After} = find_p_ending(Es, []),
 
234
            otp_xmlify_fix(After, [{p, [E2|P]}, E1 | Res]);
 
235
        true ->
 
236
            otp_xmlify_fix([E2|Es], [E1|Res])
 
237
    end;
 
238
otp_xmlify_fix([#xmlText{value="\n\n"} = E1, E2 | Es], Res) ->
 
239
    %% This is how it looks when generating a chapter from overview.edoc
 
240
    case is_paragraph(E2) of
 
241
        false ->
 
242
            {P, After} = find_p_ending(Es, []),
 
243
            otp_xmlify_fix(After, [{p, [E2|P]}, E1 | Res]);
 
244
        true ->
 
245
            otp_xmlify_fix([E2|Es], [E1|Res])
 
246
    end;
 
247
otp_xmlify_fix([E|Es], Res) ->
 
248
    otp_xmlify_fix(Es, [E|Res]);
 
249
otp_xmlify_fix([], Res) ->
 
250
    lists:reverse(Res).
 
251
 
 
252
otp_xmlify_es([E | Es]) ->
 
253
    case is_paragraph(E) of
 
254
        true ->
 
255
            case otp_xmlify_psplit(E) of
 
256
 
 
257
                %% paragraph contained inline tags and text only
 
258
                nosplit ->
 
259
                    otp_xmlify_e(E) ++ otp_xmlify_es(Es);
 
260
 
 
261
                %% paragraph contained dl, ul and/or pre and has been
 
262
                %% splitted
 
263
                SubEs ->
 
264
                    lists:flatmap(fun otp_xmlify_e/1, SubEs) ++
 
265
                        otp_xmlify_es(Es)
 
266
            end;
 
267
        false ->
 
268
            otp_xmlify_e(E) ++ otp_xmlify_es(Es)
 
269
    end;
 
270
otp_xmlify_es([]) ->
 
271
    [].
 
272
 
 
273
%% otp_xmlify_psplit(P) -> nosplit | [E]
 
274
%% Handles case 1) above.
 
275
%% Uses the {p, Es} construct, thus replaces an p xmlElement with one
 
276
%% or more {p, Es} tuples if splitting the paraghrap is necessary.
 
277
otp_xmlify_psplit(P) ->
 
278
    otp_xmlify_psplit(p_content(P), [], []).
 
279
otp_xmlify_psplit([#xmlElement{name=Name}=E | Es], Content, Res) ->
 
280
    if
 
281
        Name==blockquote; Name==ul; Name==ol; Name==dl; Name==pre;
 
282
        Name==table ->
 
283
            case Content of
 
284
                [] ->
 
285
                    otp_xmlify_psplit(Es, [], [E|Res]);
 
286
                [#xmlText{value=Str}] ->
 
287
                    %% Special case: Making a paragraph out of a blank
 
288
                    %% line isn't a great idea. Instead, this can be
 
289
                    %% viewed as the case above, where there is no
 
290
                    %% content to make a paragraph out of
 
291
                    case is_empty(Str) of
 
292
                        true ->
 
293
                            otp_xmlify_psplit(Es, [], [E|Res]);
 
294
                        false ->
 
295
                            Pnew = {p, lists:reverse(Content)},
 
296
                            otp_xmlify_psplit(Es, [], [E,Pnew|Res])
 
297
                    end;
 
298
                _ ->
 
299
                    Pnew = {p, lists:reverse(Content)},
 
300
                    otp_xmlify_psplit(Es, [], [E,Pnew|Res])
 
301
            end;
 
302
 
 
303
        true ->
 
304
            otp_xmlify_psplit(Es, [E|Content], Res)
 
305
    end;
 
306
otp_xmlify_psplit([E | Es], Content, Res) ->
 
307
    otp_xmlify_psplit(Es, [E|Content], Res);
 
308
otp_xmlify_psplit([], _Content, []) ->
 
309
    nosplit;
 
310
otp_xmlify_psplit([], [], Res) ->
 
311
    lists:reverse(Res);
 
312
otp_xmlify_psplit([], [#xmlText{value="\n\n"}], Res) ->
 
313
    lists:reverse(Res);
 
314
otp_xmlify_psplit([], Content, Res) ->
 
315
    Pnew = {p, lists:reverse(Content)},
 
316
    lists:reverse([Pnew|Res]).
 
317
 
 
318
%% otp_xmlify_e(E) -> [E]
 
319
%% This is the function which does the actual transformation of
 
320
%% single elements, normally by making sure the content corresponds
 
321
%% to what is allowed by the OTP DTDs.
 
322
%% Returns a list of elements as the xmlification in some cases
 
323
%% returns no element or more than one element (although in most cases
 
324
%% exactly one element).
 
325
otp_xmlify_e(#xmlElement{name=a} = E) ->       % 2) above
 
326
    otp_xmlify_a(E);
 
327
otp_xmlify_e(#xmlElement{name=Tag} = E)        % 3a-c)
 
328
  when Tag==b; Tag==em; Tag==pre ->
 
329
    Content = text_only(E#xmlElement.content),
 
330
    [E#xmlElement{content=Content}];
 
331
otp_xmlify_e(#xmlElement{name=code} = E) ->    % 4)
 
332
    case catch text_only(E#xmlElement.content) of
 
333
        {'EXIT', _Error} ->
 
334
            otp_xmlify_code(E);
 
335
        Content ->
 
336
            [E#xmlElement{content=Content}]
 
337
    end;
 
338
otp_xmlify_e(#xmlElement{name=Tag} = E)        % 5a
 
339
  when Tag==h1; Tag==h2; Tag==h3; Tag==h4; Tag==h5 ->
 
340
    Content = text_only(E#xmlElement.content),
 
341
    [E#xmlElement{name=b, content=Content}];
 
342
otp_xmlify_e(#xmlElement{name=Tag} = E)        % 5b-c)
 
343
  when Tag==center;
 
344
       Tag==font ->
 
345
    otp_xmlify_e(E#xmlElement.content);
 
346
otp_xmlify_e(#xmlElement{name=table} = E) ->   % 6)
 
347
    case parent(E) of
 
348
        module ->
 
349
            otp_xmlify_table(E#xmlElement.content);
 
350
        overview ->
 
351
            Content0 = otp_xmlify_e(E#xmlElement.content),
 
352
            Summary = #xmlText{value=get_attrval(summary, E)},
 
353
            TCaption = E#xmlElement{name=tcaption,
 
354
                                    attributes=[],
 
355
                                    content=[Summary]},
 
356
            Content = Content0 ++ [TCaption],
 
357
            [E#xmlElement{attributes=[], content=Content}]
 
358
    end;
 
359
otp_xmlify_e(#xmlElement{name=tbody} = E) ->
 
360
    otp_xmlify_e(E#xmlElement.content);
 
361
otp_xmlify_e(#xmlElement{name=sup} = E) ->     % 7)
 
362
    Text = get_text(E),
 
363
    [#xmlText{parents = E#xmlElement.parents,
 
364
              pos = E#xmlElement.pos,
 
365
              language = E#xmlElement.language,
 
366
              value = "(" ++ Text ++ ")"}];
 
367
otp_xmlify_e(#xmlElement{name=blockquote} = E) -> % 8)
 
368
    Content = otp_xmlify_blockquote(E#xmlElement.content),
 
369
    [E#xmlElement{content=Content}];
 
370
otp_xmlify_e(#xmlElement{name=th} = E) ->      % 9)
 
371
    Content = otp_xmlify_e(E#xmlElement.content),
 
372
    EmE = E#xmlElement{name=em, content=Content},
 
373
    [E#xmlElement{name=td, content=[EmE]}];
 
374
otp_xmlify_e(#xmlElement{name=p} = E) ->       % recurse
 
375
    Content = otp_xmlify_e(E#xmlElement.content),
 
376
    [E#xmlElement{content=Content}];
 
377
otp_xmlify_e({p, Content1}) ->
 
378
    Content2 = otp_xmlify_e(Content1),
 
379
    [{p, Content2}];
 
380
otp_xmlify_e(#xmlElement{name=ul} = E) ->
 
381
    Content = otp_xmlify_e(E#xmlElement.content),
 
382
    [E#xmlElement{content=Content}];
 
383
otp_xmlify_e(#xmlElement{name=li} = E) ->
 
384
    %% Content may need to be made into <p>s etc.
 
385
    Content = otp_xmlify(E#xmlElement.content),
 
386
    [E#xmlElement{content=Content}];
 
387
otp_xmlify_e(#xmlElement{name=dl} = E) ->
 
388
    Content0 = otp_xmlify_e(E#xmlElement.content),
 
389
    Content = otp_xmlify_dl(Content0),
 
390
    [E#xmlElement{content=Content}];
 
391
otp_xmlify_e(#xmlElement{name=dt} = E) ->
 
392
    %% Special fix: Markers in <taglist> <tag>s are not allowed,
 
393
    %% save it using 'put' and place the marker first in the <item>
 
394
    %% instead
 
395
    Content = case E#xmlElement.content of
 
396
                  [#xmlElement{name=a} = A] ->
 
397
                      put(dt_marker, otp_xmlify_e(A)),
 
398
                      otp_xmlify_e(A#xmlElement.content);
 
399
                  _ ->
 
400
                      otp_xmlify_e(E#xmlElement.content)
 
401
              end,
 
402
    [E#xmlElement{content=Content}];
 
403
otp_xmlify_e(#xmlElement{name=dd} = E) ->
 
404
    %% Content may need to be made into <p>s etc.
 
405
    Content0 = otp_xmlify(E#xmlElement.content),
 
406
    Content = case get(dt_marker) of
 
407
                  undefined -> Content0;
 
408
                  [Marker] ->
 
409
                      put(dt_marker, undefined),
 
410
                      [Marker#xmlElement{content=[]}|Content0]
 
411
              end,
 
412
    [E#xmlElement{content=Content}];
 
413
otp_xmlify_e(#xmlElement{name=tr} = E) ->
 
414
    Content = otp_xmlify_e(E#xmlElement.content),
 
415
    [E#xmlElement{content=Content}];
 
416
otp_xmlify_e(#xmlElement{name=td} = E) ->
 
417
    Content = otp_xmlify_e(E#xmlElement.content),
 
418
    [E#xmlElement{content=Content}];
 
419
otp_xmlify_e([E | Es]) ->
 
420
    otp_xmlify_e(E) ++ otp_xmlify_e(Es);
 
421
otp_xmlify_e([]) ->
 
422
    [];
 
423
otp_xmlify_e(E) ->
 
424
    [E].
 
425
 
 
426
%%--Tags with special handling------------------------------------------
 
427
 
 
428
%% otp_xmlify_a(A1) -> [A2]
 
429
%% Takes an <a> element and filters the attributes to decide wheather
 
430
%% its a seealso/url or a marker.
 
431
%% In the case of a seealso/url, the href part is checked, making
 
432
%% sure a .xml/.html file extension is removed.
 
433
%% Also, references to other applications //App has a href attribute
 
434
%% value "OTPROOT/..." (due to app_default being set to "OTPROOT")
 
435
%% , in this case both href attribute and content must be
 
436
%% formatted correctly according to requirements.
 
437
otp_xmlify_a(A) ->
 
438
    [Attr0] = filter_a_attrs(A#xmlElement.attributes),
 
439
    case Attr0 of
 
440
        #xmlAttribute{name=href, value=Href0} -> % seealso | url
 
441
            Content0 = text_only(A#xmlElement.content),
 
442
            {Href, Content} = otp_xmlify_a_href(Href0, Content0),
 
443
            [A#xmlElement{attributes=[Attr0#xmlAttribute{value=Href}],
 
444
                          content=Content}];
 
445
        #xmlAttribute{name=name} -> % marker
 
446
            Content = otp_xmlify_e(A#xmlElement.content),
 
447
            [A#xmlElement{attributes=[Attr0], content=Content}]
 
448
    end.
 
449
 
 
450
%% filter_a_attrs(Attrs) -> [Attr]
 
451
%% Removes all attributes from a <a> element except the href or
 
452
%% name attribute.
 
453
filter_a_attrs([#xmlAttribute{name=href} = Attr | _Attrs]) ->
 
454
    [Attr];
 
455
filter_a_attrs([#xmlAttribute{name=name} = Attr | _Attrs]) ->
 
456
    [Attr];
 
457
filter_a_attrs([_Attr|Attrs]) ->
 
458
    filter_a_attrs(Attrs);
 
459
filter_a_attrs([]) ->
 
460
    [].
 
461
 
 
462
%% otp_xmlify_a_href(Href0, Es0) -> {Href1, Es1}
 
463
%%   Href = string()
 
464
otp_xmlify_a_href("#"++_ = Marker, Es0) -> % <seealso marker="#what">
 
465
    {Marker, Es0};
 
466
otp_xmlify_a_href("http:"++_ = URL, Es0) -> % external URL
 
467
    {URL, Es0};
 
468
otp_xmlify_a_href("OTPROOT"++AppRef, Es0) -> % <.. marker="App:FileRef
 
469
    [AppS, "doc", FileRef1] = split(AppRef, "/"),
 
470
    FileRef = AppS++":"++otp_xmlify_a_fileref(FileRef1, AppS),
 
471
    [#xmlText{value=Str0} = T] = Es0,
 
472
    Str = case split(Str0, "/") of
 
473
              %% //Application
 
474
              [AppS2] ->
 
475
                  %% AppS2 can differ from AppS
 
476
                  %% Example: xmerl/XMerL
 
477
                  AppS2;
 
478
              [_AppS,ModRef] ->
 
479
                  case split(ModRef, ":") of
 
480
                      %% //Application/Module
 
481
                      [Module] ->
 
482
                          Module++"(3)";
 
483
                      %% //Application/Module:Type()
 
484
                      [_Module,_Type] ->
 
485
                          ModRef
 
486
                  end;
 
487
              %% //Application/Module:Function/Arity
 
488
              [_AppS,ModFunc,Arity] ->
 
489
                  ModFunc++"/"++Arity
 
490
          end,
 
491
    {FileRef, [T#xmlText{value=Str}]};
 
492
otp_xmlify_a_href("../"++File, Es0) ->
 
493
    %% Special case: This kind of relative path is used on some
 
494
    %% places within i.e. EDoc and refers to a file within the same
 
495
    %% application tree.
 
496
    %% Correct the path according to the OTP directory structure
 
497
    {"../../"++File, Es0};
 
498
otp_xmlify_a_href(FileRef1, Es0) -> % File within the same application
 
499
    FileRef2 = otp_xmlify_a_fileref(FileRef1, this),
 
500
    {FileRef2, Es0}.
 
501
 
 
502
%% otp_xmlify_a_fileref(FileRef1, AppS|this) -> FileRef2
 
503
%%   AppS = FileRef = string()
 
504
otp_xmlify_a_fileref(FileRef1, AppS) ->
 
505
    case split(FileRef1, ".#") of
 
506
 
 
507
        %% EDoc default name is "overview-summary.html,
 
508
        %% name of OTP User's Guide chapter is "chapter.xml"
 
509
        ["overview-summary", _Ext] ->
 
510
            "chapter";
 
511
        ["overview-summary", _Ext, Marker] ->
 
512
            "chapter#"++Marker;
 
513
 
 
514
        [File, Ext] when Ext=="xml";
 
515
                         Ext=="html", AppS/=this ->
 
516
            File;
 
517
        [File, Ext, Marker0] ->
 
518
            %% Here is an awkward solution to an awkward problem
 
519
            %% The marker automatically inserted at each function 
 
520
            %% does not seem to work for EDoc generated ERLREFs.
 
521
            %% So if the referenced marker is in an ERLREF generated
 
522
            %% by EDoc, keep it "as is", ie "function-arity".
 
523
            %% If the referenced marker is NOT in an ERLREF generated
 
524
            %% by EDoc, the marker should be on the format
 
525
            %% "function/arity".
 
526
            %% The awkward part of the solution is to decide wheather
 
527
            %% the ERLREF is generated by EDoc or not: Here we make
 
528
            %% the decision based on which application the module
 
529
            %% belongs to -- which is ok when the module was written
 
530
            %% but probably not in the future...
 
531
            EDocApps = ["edoc","hipe","syntax_tools","xmerl"],
 
532
            IsEDocGenerated = lists:member(AppS, EDocApps),
 
533
            Marker = if
 
534
                         %% The marker is in a file in *this*
 
535
                         %% application (which documentation obviously
 
536
                         %% is generated by EDoc), or it is in a file
 
537
                         %% in an application which documentation
 
538
                         %% is assumed to be generated by EDoc
 
539
                         AppS==this; IsEDocGenerated ->
 
540
                             Marker0;
 
541
 
 
542
                         %% The marker is in a file in an application
 
543
                         %% which documentation is assumed NOT to be
 
544
                         %% generated by EDoc
 
545
                         true ->
 
546
                             case split(Marker0, "-") of
 
547
                                 [Func,Arity] ->
 
548
                                     Func++"/"++Arity;
 
549
                                 _ ->
 
550
                                     Marker0
 
551
                             end
 
552
                     end,
 
553
            if
 
554
                %% Ignore file extension in file reference if it either
 
555
                %% is ".xml" or if it is ".html" but AppS/=this, that
 
556
                %% is, we're resolving an OTPROOT file reference
 
557
                Ext=="xml";
 
558
                Ext=="html", AppS/=this ->
 
559
                    File++"#"++Marker;
 
560
                true ->
 
561
                    File++"."++Ext++"#"++Marker
 
562
            end;
 
563
 
 
564
        %% References to other files than XML files are kept as-is
 
565
        _ ->
 
566
            FileRef1
 
567
    end.
 
568
 
 
569
%% otp_xmlify_blockquote(Es1) -> Es2
 
570
%% Ensures that the content of a <blockquote> is divided into
 
571
%% <p>s using the {p, Es} construct.
 
572
otp_xmlify_blockquote([#xmlElement{name=p} = E|Es]) ->
 
573
    [E | otp_xmlify_blockquote(Es)];
 
574
otp_xmlify_blockquote([#xmlText{} = E|Es]) ->
 
575
    {P, After} = find_p_ending(Es, []),
 
576
    [{p, [E|P]} | otp_xmlify_blockquote(After)];
 
577
otp_xmlify_blockquote([]) ->
 
578
    [].
 
579
 
 
580
%% otp_xmlify_code(E) -> Es
 
581
%% Takes a <code> xmlElement and split it into a list of <code> and
 
582
%% other xmlElements. Necessary when it contains more than a single
 
583
%% xmlText element.
 
584
%% Example:
 
585
%% #xmlElement{name=code,
 
586
%%             content=[#xmlText{}, #xmlElement{name=br}, #xmlText{}]}
 
587
%% =>
 
588
%% [#xmlElement{name=code, content=[#xmlText{}]},
 
589
%%  #xmlElement{name=br},
 
590
%%  #xmlElement{name=code, content=[#xmlText{}]}]
 
591
otp_xmlify_code(E) ->
 
592
    otp_xmlify_code(E, E#xmlElement.content, []).
 
593
otp_xmlify_code(Code, [#xmlText{} = E|Es], Acc) ->
 
594
    otp_xmlify_code(Code, Es, [Code#xmlElement{content=[E]}|Acc]);
 
595
otp_xmlify_code(Code, [#xmlElement{} = E|Es], Acc) ->
 
596
    otp_xmlify_code(Code, Es, [E|Acc]);
 
597
otp_xmlify_code(_Code, [], Acc) ->
 
598
    lists:reverse(Acc).
 
599
 
 
600
%% otp_xmlify_dl(Es1) -> Es2
 
601
%% Insert empty <dd> elements if necessary.
 
602
%% OTP DTDs does not allow <taglist>s with <tag>s but no <item>s.
 
603
otp_xmlify_dl([#xmlElement{name=dt} = E|Es]) ->
 
604
    [E|otp_xmlify_dl(Es, E)];
 
605
otp_xmlify_dl([E|Es]) ->
 
606
    [E|otp_xmlify_dl(Es)];
 
607
otp_xmlify_dl([]) ->
 
608
    [].
 
609
 
 
610
otp_xmlify_dl([#xmlElement{name=dd} = E|Es], _DT) ->
 
611
    [E|otp_xmlify_dl(Es)];
 
612
otp_xmlify_dl([#xmlElement{name=dt} = E|Es], DT) ->
 
613
    DD = DT#xmlElement{name=dd, attributes=[], content=[]},
 
614
    [DD,E|otp_xmlify_dl(Es, E)];
 
615
otp_xmlify_dl([E|Es], DT) ->
 
616
    [E|otp_xmlify_dl(Es, DT)];
 
617
otp_xmlify_dl([], DT) ->
 
618
    DD = DT#xmlElement{name=dd, attributes=[], content=[]},
 
619
    [DD].
 
620
 
 
621
%% otp_xmlify_table(Es1) -> Es2
 
622
%% Transform <table> contents into "text", that is, inline elements.
 
623
otp_xmlify_table([#xmlText{} = E|Es]) ->
 
624
    [E | otp_xmlify_table(Es)];
 
625
otp_xmlify_table([#xmlElement{name=tbody} = E|Es]) ->
 
626
    otp_xmlify_table(E#xmlElement.content)++otp_xmlify_table(Es);
 
627
otp_xmlify_table([#xmlElement{name=tr, content=Content}|Es]) ->
 
628
    %% Insert newlines between table rows
 
629
    otp_xmlify_table(Content)++[{br,[]}]++otp_xmlify_table(Es);
 
630
otp_xmlify_table([#xmlElement{name=th, content=Content}|Es]) ->
 
631
    [{em, Content} | otp_xmlify_table(Es)];
 
632
otp_xmlify_table([#xmlElement{name=td, content=Content}|Es]) ->
 
633
    otp_xmlify_e(Content) ++ otp_xmlify_table(Es);
 
634
otp_xmlify_table([]) ->
 
635
    [].
 
636
 
 
637
%%--Misc help functions used by otp_xmlify/1 et al---------------------
 
638
 
 
639
%% find_next(Tag, Es) -> {Es1, Es2}
 
640
%% Returns {Es1, Es2} where Es1 is the list of all elements up to (but
 
641
%% not including) the first element with tag Tag in Es, and Es2
 
642
%% is the remaining elements of Es.
 
643
find_next(Tag, Es) ->
 
644
    find_next(Tag, Es, []).
 
645
find_next(Tag, [#xmlElement{name=Tag} = E | Es], AccEs) ->
 
646
    {lists:reverse(AccEs), [E|Es]};
 
647
find_next(Tag, [E|Es], AccEs) ->
 
648
    find_next(Tag, Es, [E|AccEs]);
 
649
find_next(_Tag, [], AccEs) ->
 
650
    {lists:reverse(AccEs), []}.
 
651
 
 
652
%% find_p_ending(Es, []) -> {Es1, Es2}
 
653
%% Returns {Es1, Es2} where Es1 is the list of all elements up to (but
 
654
%% not including) the first paragraph break in Es, and Es2 is
 
655
%% the remaining elements of Es2.
 
656
%% Paragraph break = <p> tag or empty line
 
657
%% the next blank line, <p> or end-of-list as P, and the remaining
 
658
%% elements of Es as After.
 
659
find_p_ending([#xmlText{value="\n \n"++_} = E|Es], P) ->
 
660
    {lists:reverse(P), [E|Es]};
 
661
find_p_ending([#xmlElement{name=p} = E|Es], P) ->
 
662
    {lists:reverse(P), [E|Es]};
 
663
find_p_ending([E|Es], P) ->
 
664
    find_p_ending(Es, [E|P]);
 
665
find_p_ending([], P) ->
 
666
    {lists:reverse(P), []}.
 
667
 
 
668
%% is_paragraph(E | P) -> bool()
 
669
%%   P = {p, Es}
 
670
is_paragraph(#xmlElement{name=p}) -> true;
 
671
is_paragraph({p, _Es}) -> true;
 
672
is_paragraph(_E) -> false.
 
673
 
 
674
%% p_content(E | P) -> Es
 
675
p_content(#xmlElement{content=Content}) -> Content;
 
676
p_content({p, Content}) -> Content.
 
677
 
 
678
%% is_empty(Str) -> bool()
 
679
%%   Str = string()
 
680
%% Returns true if Str is empty in the sense that it contains nothing
 
681
%% but spaces, tabs or newlines.
 
682
is_empty("\n"++Str) ->
 
683
    is_empty(Str);
 
684
is_empty(" "++Str) ->
 
685
    is_empty(Str);
 
686
is_empty("\t"++Str) ->
 
687
    is_empty(Str);
 
688
is_empty("") ->
 
689
    true;
 
690
is_empty(_) ->
 
691
    false.
 
692
 
 
693
%% split(Str, Seps) -> [Str]
 
694
split(Str, Seps) ->
 
695
    split(Str, Seps, []).
 
696
 
 
697
split([Ch|Str], Seps, Acc) ->
 
698
    case lists:member(Ch, Seps) of
 
699
        true ->  split(Str, Seps, Acc);
 
700
        false -> split(Str, Seps, Acc, [Ch])
 
701
    end;
 
702
split([], _Seps, Acc) ->
 
703
    lists:reverse(Acc).
 
704
 
 
705
split([Ch|Str], Seps, Acc, Chs) ->
 
706
    case lists:member(Ch, Seps) of
 
707
        true ->  split(Str, Seps, [lists:reverse(Chs)|Acc]);
 
708
        false -> split(Str, Seps, Acc, [Ch|Chs])
 
709
    end;
 
710
split([], _Seps, Acc, Chs) ->
 
711
    lists:reverse([lists:reverse(Chs)|Acc]).
 
712
 
 
713
%%--Functions for creating an erlref document---------------------------
 
714
 
 
715
%% function_name(F) -> string()
 
716
%%   F = #xmlElement{name=function}
 
717
%% Returns the name of a function as "name/arity".
 
718
function_name(E) ->
 
719
    get_attrval(name, E) ++ "/" ++ get_attrval(arity, E).
 
720
 
 
721
%% functions(Fs) -> Es
 
722
%%   Fs = [{Name, F}]
 
723
%%     Name = string()  "name/arity"
 
724
%%     F = #xmlElement{name=function}
 
725
functions(Fs) ->
 
726
    Es = lists:flatmap(fun ({Name, E}) -> function(Name, E) end, Fs),
 
727
    if
 
728
        Es==[] ->
 
729
            [];
 
730
        true ->
 
731
            {funcs, Es}
 
732
    end.
 
733
 
 
734
function(_Name, E=#xmlElement{content = Es}) ->
 
735
    TypeSpec = get_content(typespec, Es),
 
736
    [?NL,{func, [ ?NL,
 
737
                  {name, 
 
738
                          case funcheader(TypeSpec) of
 
739
                              [] ->
 
740
                                  signature(get_content(args, Es),
 
741
                                            get_attrval(name, E));
 
742
                              Spec -> Spec
 
743
                          end
 
744
                         },
 
745
                  ?NL,{fsummary, fsummary(Es)},
 
746
                  ?NL,local_types(TypeSpec),
 
747
                  ?NL,{desc,
 
748
                       label_anchor(E)++
 
749
                       deprecated(Es)++
 
750
                       fulldesc(Es)++
 
751
                       seealso_function(Es)}
 
752
           ]}].
 
753
 
 
754
fsummary([]) -> ["\s"];
 
755
fsummary(Es) ->
 
756
    Desc = get_content(description, Es),
 
757
    case get_content(briefDescription, Desc) of
 
758
        [] ->
 
759
            fsummary_equiv(Es);    % no description at all if no equiv
 
760
        ShortDesc ->
 
761
            text_only(ShortDesc)
 
762
    end.
 
763
 
 
764
fsummary_equiv(Es) ->
 
765
    case get_content(equiv, Es) of
 
766
        [] -> ["\s"];
 
767
        Es1 ->
 
768
            case get_content(expr, Es1) of
 
769
                [] -> ["\s"];
 
770
                [Expr] ->
 
771
                    ["Equivalent to ", Expr, ".",?NL]
 
772
            end
 
773
    end.
 
774
 
 
775
label_anchor(E) ->
 
776
    case get_attrval(label, E) of
 
777
        "" -> [];
 
778
        Ref -> [{marker, [{id, Ref}],[]},?NL]
 
779
    end.
 
780
 
 
781
label_anchor(Content, E) ->
 
782
    case get_attrval(label, E) of
 
783
        "" -> Content;
 
784
        Ref -> {p,[{marker, [{id, Ref}],[]},
 
785
                   {em, Content}]}
 
786
    end.
 
787
 
 
788
signature(Es, Name) -> 
 
789
    [Name, "("] ++ seq(fun arg/1, Es) ++ [") -> term()", ?NL].
 
790
 
 
791
arg(#xmlElement{content = Es}) ->
 
792
    [get_text(argName, Es)].
 
793
 
 
794
funcheader([]) -> [];
 
795
funcheader(Es) ->
 
796
    [t_name(get_elem(erlangName, Es))] ++ t_utype(get_elem(type, Es)).
 
797
 
 
798
local_types([]) -> [];
 
799
local_types(Es) ->
 
800
    local_defs2(get_elem(localdef, Es)).
 
801
 
 
802
local_defs2([]) -> [];
 
803
local_defs2(Es) ->
 
804
    {type,[?NL | [{v, localdef2(E)} || E <- Es]]}.
 
805
 
 
806
%% Like localdef/1, but does not use label_anchor/2 -- we don't want any
 
807
%% markers or em tags in <v> tag, plain text only!
 
808
localdef2(#xmlElement{content = Es}) ->
 
809
    case get_elem(typevar, Es) of
 
810
        [] -> 
 
811
            t_utype(get_elem(type, Es));
 
812
        [V] ->
 
813
            t_var(V) ++ [" = "] ++ t_utype(get_elem(type, Es))
 
814
    end.
 
815
 
 
816
type_name(#xmlElement{content = Es}) ->
 
817
    t_name(get_elem(erlangName, get_content(typedef, Es))).
 
818
 
 
819
types(Ts) ->
 
820
    Es = lists:flatmap(fun ({Name, E}) -> typedecl(Name, E) end, Ts),
 
821
    [?NL, {taglist,[?NL|Es]}].
 
822
 
 
823
typedecl(Name, #xmlElement{content = Es}) ->
 
824
    TypedefEs = get_content(typedef, Es),
 
825
    Id = "type-"++Name,
 
826
    [{tag, typedef(TypedefEs)},
 
827
     ?NL,
 
828
     {item, [{marker,[{id,Id}],[]} |
 
829
             local_defs(get_elem(localdef, TypedefEs)) ++ fulldesc(Es)]},
 
830
     ?NL].
 
831
 
 
832
typedef(Es) ->
 
833
    Name = ([t_name(get_elem(erlangName, Es)), "("]
 
834
            ++ seq(fun t_utype_elem/1, get_content(argtypes, Es), [")"])),
 
835
    case get_elem(type, Es) of
 
836
         [] ->
 
837
            [{tt, Name}];
 
838
         Type ->
 
839
            [{tt, Name ++ [" = "] ++ t_utype(Type)}]
 
840
    end.
 
841
 
 
842
local_defs([]) -> [];
 
843
local_defs(Es) ->
 
844
    [?NL, {ul, [{li, [{tt, localdef(E)}]} || E <- Es]}].
 
845
 
 
846
localdef(E = #xmlElement{content = Es}) ->
 
847
    Var = case get_elem(typevar, Es) of
 
848
              [] -> 
 
849
                  [label_anchor(t_abstype(get_content(abstype, Es)), E)];
 
850
              [V] ->
 
851
                  t_var(V)
 
852
          end,
 
853
    Var ++ [" = "] ++ t_utype(get_elem(type, Es)).
 
854
 
 
855
deprecated(Es) ->
 
856
    case get_content(deprecated, Es) of
 
857
        [] -> [];
 
858
        DeprEs ->
 
859
            Es2 = get_content(fullDescription,
 
860
                              get_content(description, DeprEs)),
 
861
            Es3 = otp_xmlify_e(Es2),
 
862
            [{p, [{em, ["This function is deprecated: "]} |Es3]}, ?NL]
 
863
    end.
 
864
 
 
865
fulldesc(Es) ->
 
866
    case get_content(fullDescription, get_content(description, Es)) of
 
867
        [] ->
 
868
            index_desc(Es);
 
869
        Desc ->
 
870
            [?NL|otp_xmlify(Desc)] ++ [?NL]
 
871
    end.
 
872
 
 
873
index_desc(Es) ->
 
874
    Desc = get_content(description, Es),
 
875
    case get_content(briefDescription, Desc) of
 
876
        [] ->
 
877
            equiv(Es);    % no description at all if no equiv
 
878
        ShortDesc ->
 
879
            ShortDesc
 
880
    end.
 
881
 
 
882
seealso_module(Es) ->
 
883
    case get_elem(see, Es) of
 
884
        [] -> [];
 
885
        Es1 ->
 
886
            {section,[{title,["See also"]},{p,seq(fun see/1, Es1, [])}]}
 
887
    end.
 
888
seealso_function(Es) ->
 
889
    case get_elem(see, Es) of
 
890
        [] -> [];
 
891
        Es1 ->
 
892
            [{p, [{em, ["See also:"]}, " "] ++ seq(fun see/1, Es1, ["."])},
 
893
             ?NL]
 
894
    end.
 
895
 
 
896
%% ELEMENT see PCDATA
 
897
%% ATTLIST name PCDATA
 
898
%%         href PCDATA
 
899
see(#xmlElement{content=Es0} = E) ->
 
900
    Href0 = get_attrval(href, E),
 
901
    {Href, Es} = otp_xmlify_a_href(Href0, Es0),
 
902
    [{seealso, [{marker, Href}], Es}].
 
903
    
 
904
equiv(Es) ->
 
905
    case get_content(equiv, Es) of
 
906
        [] -> ["\s"];
 
907
        Es1 ->
 
908
            case get_content(expr, Es1) of
 
909
                [] -> [];
 
910
                [Expr] ->
 
911
                    Expr1 = [Expr],
 
912
                    Expr2 = case get_elem(see, Es1) of
 
913
                                [] ->
 
914
                                    {c,Expr1};
 
915
                                [E=#xmlElement{}] ->
 
916
                                    case get_attrval(href, E) of
 
917
                                        "" ->
 
918
                                            {c,Expr1};
 
919
                                        Ref ->
 
920
                                            {seealso, [{marker, Ref}], Expr1}
 
921
                                    end
 
922
                            end,
 
923
                    [{p, ["Equivalent to ", Expr2, "."]}, ?NL]
 
924
            end
 
925
    end.
 
926
 
 
927
authors(Es) ->
 
928
    case get_elem(author, Es) of
 
929
        [] ->
 
930
            [?NL,{aname,["\s"]},?NL,{email,["\s"]}];
 
931
        Es1 ->
 
932
            [?NL|seq(fun author/1, Es1, "", [])]
 
933
    end.
 
934
 
 
935
author(E=#xmlElement{}) ->
 
936
    Name = case get_attrval(name, E) of
 
937
               [] -> "\s";
 
938
               N -> N
 
939
           end,
 
940
    Mail = case get_attrval(email, E) of
 
941
               [] -> "\s";
 
942
               M -> M
 
943
           end,
 
944
    [?NL,{aname,[Name]},?NL,{email,[Mail]}].
 
945
 
 
946
t_name([E]) ->
 
947
    N = get_attrval(name, E),
 
948
    case get_attrval(module, E) of
 
949
        "" -> N;
 
950
        M ->
 
951
            S = M ++ ":" ++ N,
 
952
            case get_attrval(app, E) of
 
953
                "" -> S;
 
954
                A -> "//" ++ A ++ "/" ++ S
 
955
            end
 
956
    end.
 
957
 
 
958
t_utype([E]) ->
 
959
    t_utype_elem(E).
 
960
 
 
961
t_utype_elem(E=#xmlElement{content = Es}) ->
 
962
    case get_attrval(name, E) of
 
963
        "" -> t_type(Es);
 
964
        Name ->
 
965
            T = t_type(Es),
 
966
            case T of
 
967
                [Name] -> T;    % avoid generating "Foo::Foo"
 
968
                T -> [Name] ++ ["::"] ++ T
 
969
            end
 
970
    end.
 
971
 
 
972
t_type([E=#xmlElement{name = typevar}]) ->
 
973
    t_var(E);
 
974
t_type([E=#xmlElement{name = atom}]) ->
 
975
    t_atom(E);
 
976
t_type([E=#xmlElement{name = integer}]) ->
 
977
    t_integer(E);
 
978
t_type([E=#xmlElement{name = float}]) ->
 
979
    t_float(E);
 
980
t_type([#xmlElement{name = nil}]) ->
 
981
    t_nil();
 
982
t_type([#xmlElement{name = list, content = Es}]) ->
 
983
    t_list(Es);
 
984
t_type([#xmlElement{name = tuple, content = Es}]) ->
 
985
    t_tuple(Es);
 
986
t_type([#xmlElement{name = 'fun', content = Es}]) ->
 
987
    t_fun(Es);
 
988
t_type([#xmlElement{name = abstype, content = Es}]) ->
 
989
    t_abstype(Es);
 
990
t_type([#xmlElement{name = union, content = Es}]) ->
 
991
    t_union(Es);
 
992
t_type([#xmlElement{name = record, content = Es}]) ->
 
993
    t_record(Es).
 
994
 
 
995
t_var(E) ->
 
996
    [get_attrval(name, E)].
 
997
 
 
998
t_atom(E) ->
 
999
    [get_attrval(value, E)].
 
1000
 
 
1001
t_integer(E) ->
 
1002
    [get_attrval(value, E)].
 
1003
 
 
1004
t_float(E) ->
 
1005
    [get_attrval(value, E)].
 
1006
 
 
1007
t_nil() ->
 
1008
    ["[]"].
 
1009
 
 
1010
t_list(Es) ->
 
1011
    ["["] ++ t_utype(get_elem(type, Es)) ++ ["]"].
 
1012
 
 
1013
t_tuple(Es) ->
 
1014
    ["{"] ++ seq(fun t_utype_elem/1, Es, ["}"]).
 
1015
 
 
1016
t_fun(Es) ->
 
1017
    ["("] ++ seq(fun t_utype_elem/1, get_content(argtypes, Es),
 
1018
                 [") -> "] ++ t_utype(get_elem(type, Es))).
 
1019
 
 
1020
t_record([E|Es]) ->
 
1021
    ["#", get_attrval(value, E), "{"++ seq(fun t_field/1, Es) ++"}"].
 
1022
t_field(#xmlElement{name=field, content=[Atom,Type]}) ->
 
1023
    [get_attrval(value, Atom), "="] ++ t_utype_elem(Type).
 
1024
 
 
1025
t_abstype(Es) ->
 
1026
    case split_at_colon(t_name(get_elem(erlangName, Es)),[]) of
 
1027
        {Mod,Type} -> 
 
1028
            [Type, "("] ++ 
 
1029
                seq(fun t_utype_elem/1, get_elem(type, Es), [")"]) ++ 
 
1030
                [" (see module ", Mod, ")"];
 
1031
        Type ->
 
1032
            [Type, "("] ++ 
 
1033
                seq(fun t_utype_elem/1, get_elem(type, Es), [")"])
 
1034
    end.
 
1035
 
 
1036
%% Split at one colon, but not at two (or more)
 
1037
split_at_colon([$:,$:|_]=Rest,Acc) ->
 
1038
    lists:reverse(Acc)++Rest;
 
1039
split_at_colon([$:|Type],Acc) ->
 
1040
    {lists:reverse(Acc),Type};
 
1041
split_at_colon([Char|Rest],Acc) ->
 
1042
    split_at_colon(Rest,[Char|Acc]);
 
1043
split_at_colon([],Acc) ->
 
1044
    lists:reverse(Acc).
 
1045
 
 
1046
t_union(Es) ->
 
1047
    seq(fun t_utype_elem/1, Es, " | ", []).
 
1048
 
 
1049
%% seq(Fun, Es)
 
1050
%% seq(Fun, Es, Tail)
 
1051
%% seq(Fun, Es, Sep, Tail) -> [string()]
 
1052
%%   Fun = function(E) -> [string()]
 
1053
%%   Sep = string()
 
1054
%%   Tail = [string()]
 
1055
%% Applies Fun to each element E in Es and return the appended list of
 
1056
%% strings, separated by Sep which defaults to ", " and ended by Tail
 
1057
%% which defaults to [].
 
1058
seq(Fun, Es) ->
 
1059
    seq(Fun, Es, []).
 
1060
seq(Fun, Es, Tail) ->
 
1061
    seq(Fun, Es, ", ", Tail).
 
1062
seq(Fun, [E], _Sep, Tail) ->
 
1063
    Fun(E) ++ Tail;
 
1064
seq(Fun, [E | Es], Sep, Tail) ->
 
1065
    Fun(E) ++ [Sep] ++ seq(Fun, Es, Sep, Tail);
 
1066
seq(_Fun, [], _Sep, Tail) ->
 
1067
    Tail.
 
1068
 
 
1069
%%--Misc functions for accessing fields etc-----------------------------
 
1070
 
 
1071
%% Type definitions used below:
 
1072
%%   E = #xmlElement{} | #xmlText{}
 
1073
%%   Es = [E]
 
1074
%%   Tag = atom(), XHTML tag
 
1075
%%   Name = atom(), XHTML attribute name
 
1076
%%   Attrs = [#xmlAttribute{}]
 
1077
%%   Ts = [#xmlText{}]
 
1078
 
 
1079
%% parent(E) -> module | overview
 
1080
parent(E) ->
 
1081
    Parents = E#xmlElement.parents,
 
1082
    {Parent,_} = lists:last(Parents),
 
1083
    Parent.
 
1084
 
 
1085
%% get_elem(Tag, Es1) -> Es2
 
1086
%% Returns a list of all elements in Es which have the name Tag.
 
1087
get_elem(Name, [#xmlElement{name = Name} = E | Es]) ->
 
1088
    [E | get_elem(Name, Es)];
 
1089
get_elem(Name, [_ | Es]) ->
 
1090
    get_elem(Name, Es);
 
1091
get_elem(_, []) ->
 
1092
    [].
 
1093
 
 
1094
%% get_attr(Name, Attrs1) -> Attrs2
 
1095
%% Returns a list of all attributes in Attrs1 which have the name Name.
 
1096
get_attr(Name, [#xmlAttribute{name = Name} = A | As]) ->
 
1097
    [A | get_attr(Name, As)];
 
1098
get_attr(Name, [_ | As]) ->
 
1099
    get_attr(Name, As);
 
1100
get_attr(_, []) ->
 
1101
    [].
 
1102
 
 
1103
%% get_attrval(Name, E) -> string()
 
1104
%% If E has one attribute with name Name, return its value, otherwise ""
 
1105
get_attrval(Name, #xmlElement{attributes = As}) ->
 
1106
    case get_attr(Name, As) of
 
1107
        [#xmlAttribute{value = V}] ->
 
1108
            V;
 
1109
        [] -> ""
 
1110
    end.
 
1111
 
 
1112
%% get_content(Tag, Es1) -> Es2
 
1113
%% If there is one element in Es1 with name Tag, returns its contents,
 
1114
%% otherwise []
 
1115
get_content(Name, Es) ->
 
1116
    case get_elem(Name, Es) of
 
1117
        [#xmlElement{content = Es1}] ->
 
1118
            Es1;
 
1119
        [] -> []
 
1120
    end.
 
1121
 
 
1122
%% get_text(Tag, Es) -> string()
 
1123
%% If there is one element in Es with name Tag, and its content is 
 
1124
%% a single xmlText, return the value of this xmlText.
 
1125
%% Otherwise return "".
 
1126
get_text(Name, Es) ->
 
1127
    case get_content(Name, Es) of
 
1128
        [#xmlText{value = Text}] ->
 
1129
            Text;
 
1130
        [] -> ""
 
1131
    end.
 
1132
 
 
1133
%% get_text(E) -> string()
 
1134
%% Return the value of an single xmlText which is the content of E,
 
1135
%% possibly recursively.
 
1136
get_text(#xmlElement{content=[#xmlText{value=Text}]}) ->
 
1137
    Text;
 
1138
get_text(#xmlElement{content=[E]}) ->
 
1139
    get_text(E).
 
1140
 
 
1141
%% text_only(Es) -> Ts
 
1142
%% Takes a list of xmlElement and xmlText and return a lists of xmlText.
 
1143
text_only([#xmlElement{content = Content}|Es]) ->
 
1144
    text_only(Content) ++ text_only(Es);
 
1145
text_only([#xmlText{} = E |Es]) ->
 
1146
    [E | text_only(Es)];
 
1147
text_only([]) ->
 
1148
    [].