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

« back to all changes in this revision

Viewing changes to lib/xmerl/doc/examples/test_html.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.0, (the "License"); you may not use this file except in
 
3
%%% compliance with the License. You may obtain a copy of the License at
 
4
%%% http://www.erlang.org/license/EPL1_0.txt
 
5
%%%
 
6
%%% Software distributed under the License is distributed on an "AS IS"
 
7
%%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
8
%%% the License for the specific language governing rights and limitations
 
9
%%% under the License.
 
10
%%%
 
11
%%% The Original Code is xmerl-0.7
 
12
%%%
 
13
%%% The Initial Developer of the Original Code is Ericsson Telecom
 
14
%%% AB. Portions created by Ericsson are Copyright (C), 1998, Ericsson
 
15
%%% Telecom AB. All Rights Reserved.
 
16
%%%
 
17
%%% Contributor(s): ______________________________________.
 
18
%%%
 
19
%%%----------------------------------------------------------------------
 
20
%%% #0.    BASIC INFORMATION
 
21
%%%----------------------------------------------------------------------
 
22
%%% File:        test_html.erl
 
23
%%% Author       : Ulf Wiger <ulf.wiger@ericsson.com>
 
24
 
 
25
%%% Description  : Callback module for exporting XML to HTML with support
 
26
%%%                for special Erlang-related tags. (Experimental)
 
27
%%% 
 
28
%%% Modules used : lists, io_lib
 
29
%%% 
 
30
%%%----------------------------------------------------------------------
 
31
 
 
32
-module(test_html).
 
33
-author('ulf.wiger@ericsson.com').
 
34
 
 
35
 
 
36
-export(['#xml-inheritance#'/0]).
 
37
 
 
38
%%% special Erlang forms
 
39
-export(['EXIT'/4,
 
40
         'tuple_list'/4]).
 
41
 
 
42
-export(['#root#'/4,
 
43
         title/4,
 
44
         heading/4,
 
45
         section/4,
 
46
         table/4,
 
47
         row/4,
 
48
         col/4,
 
49
         data/4,
 
50
         p/4, para/4, 'P'/4,
 
51
         emphasis/4]).
 
52
 
 
53
-include("xmerl.hrl").
 
54
 
 
55
 
 
56
'#xml-inheritance#'() -> [xmerl_xml].
 
57
 
 
58
 
 
59
 
 
60
%% The '#root#' tag is called when the entire structure has been exported.
 
61
%% It does not appear in the structure itself.
 
62
'#root#'(Data, Attrs, [], E) ->
 
63
    Title = 
 
64
        case find_attribute(title, Attrs) of
 
65
            {value, T} ->
 
66
                ["<title>", T, "</title>"];
 
67
            false ->
 
68
                []
 
69
        end,
 
70
    ["<!DOCTYPE HTML PUBLIC \"-//IETF//DTD HTML//EN\">\n"
 
71
     "<html>\n",
 
72
     "<head>\n", Title, "</head>\n"
 
73
     "<body>\n", Data, "</body>\n"].
 
74
 
 
75
 
 
76
 
 
77
 
 
78
%%% Special token: EXIT
 
79
'EXIT'(Reason, Attrs = [], Parents = [], E) ->
 
80
    %% This happens e.g. if a request function crashes completely.
 
81
    ["<pre>\n", mk_string({'EXIT', Reason}), "</pre>"].
 
82
 
 
83
 
 
84
title(Str, Attrs, Parents, E) ->
 
85
    ["<h1>", Str, "</h1>\n"].
 
86
 
 
87
 
 
88
%%% section/3 is to be used instead of headings.
 
89
section(Data, Attrs, [{section,_}, {section,_}, {section,_} | _], E) ->
 
90
    opt_heading(Attrs, "<h4>", "</h4>", Data);
 
91
section(Data, Attrs, [{section,_}, {section,_} | _], E) ->
 
92
    opt_heading(Attrs, "<h3>", "</h3>", Data);
 
93
section(Data, Attrs, [{section,_} | _], E) ->
 
94
    opt_heading(Attrs, "<h2>", "</h2>", Data);
 
95
section(Data, Attrs, Parents, E) ->
 
96
    opt_heading(Attrs, "<h1>", "</h1>", Data).
 
97
 
 
98
opt_heading(Attrs, StartTag, EndTag, Data) ->
 
99
    case find_attribute(heading, Attrs) of
 
100
        {value, Text} ->
 
101
            [StartTag, Text, EndTag, "\n" | Data];
 
102
        false ->
 
103
            Data
 
104
    end.
 
105
 
 
106
 
 
107
%% tables
 
108
%% e.g. {table, [{heading, [{col, H1}, {col, H2}]},
 
109
%%               {row, [{col, C11}, {col, C12}]},
 
110
%%               {row, [{col, C21}, {col, C22}]}]}.
 
111
                             
 
112
table(Data, Attrs, Parents, E) ->
 
113
    Border = case find_attribute(border, Attrs) of
 
114
                 false ->
 
115
                     " border=1";
 
116
                 {value, N} ->
 
117
                     [" border=", mk_string(N)]
 
118
             end,
 
119
    ["<table", Border, ">\n", Data, "\n</table>\n"].
 
120
 
 
121
row(Data, Attrs, [{table,_}|_], E) ->
 
122
    ["<tr>", Data, "</tr>\n"].
 
123
 
 
124
heading(Data, Attrs, [{table,_}|_], E) ->
 
125
    ["<tr>", Data, "</tr>\n"].
 
126
 
 
127
 
 
128
%% Context-sensitive columns (heading- or row columns)
 
129
col(Data, Attrs, [{heading,_}, {table,_} | _], E) ->
 
130
    ["<th>", nbsp_if_empty(Data), "</th>\n"];
 
131
col(Data, Attrs, [{row,_}, {table,_} | _], E) ->
 
132
    ["<td>", nbsp_if_empty(Data), "</td>\n"].
 
133
 
 
134
 
 
135
tuple_list(List, Attrs, Parents, E) ->
 
136
    Elems = case find_attribute(elements, Attrs) of
 
137
                {value, Es} -> 
 
138
                    Es;
 
139
                false ->
 
140
                    case List of
 
141
                        [H|_] ->
 
142
                            lists:seq(1,size(H));
 
143
                        [] ->
 
144
                            []
 
145
                    end
 
146
            end,
 
147
    TableData = [{row, [{col, {element(P, Rec)}} || P <- Elems]} ||
 
148
                    Rec <- List],
 
149
    Table = case find_attribute(heading, Attrs) of
 
150
                {value, Cols} ->
 
151
                    Head = {heading, [{col, C} || C <- Cols]},
 
152
                    {table, [Head | TableData]};
 
153
                false ->
 
154
                    {table, TableData}
 
155
            end,
 
156
    {'#xml-redefine#', Table}.
 
157
 
 
158
 
 
159
data(Data, Pos, Attrs, Parents) ->
 
160
    mk_string(Data).
 
161
 
 
162
 
 
163
 
 
164
p(Data, Pos, Attrs, Parents) ->
 
165
    {'#xml-alias#', 'P'}.
 
166
 
 
167
para(Data, Pos, Attrs, Parents) ->
 
168
    {'#xml-alias#', 'P'}.
 
169
 
 
170
'P'(Data, Pos, Attrs, Parents) ->
 
171
    ["<p>", mk_string(Data), "</p>\n"].
 
172
 
 
173
 
 
174
emphasis(Str, Pos, Attrs, Parents) ->
 
175
    ["<strong>", Str, "</strong>"].
 
176
 
 
177
 
 
178
nbsp_if_empty(Data) when binary(Data), size(Data) == 0 ->
 
179
    "&nbsp;";
 
180
nbsp_if_empty(Data) when list(Data) ->
 
181
    case catch list_to_binary(Data) of
 
182
        {'EXIT', _} ->
 
183
            nbsp_if_empty_term(Data);
 
184
        B when size(B) == 0 ->
 
185
            "&nbsp;";
 
186
        _ ->
 
187
            Data
 
188
    end;
 
189
nbsp_if_empty(Data) ->
 
190
    nbsp_if_empty_term(Data).
 
191
 
 
192
nbsp_if_empty_term(Data) ->
 
193
    Str = io_lib:format("~p", [Data]),
 
194
    case list_to_binary(Str) of
 
195
        B when size(B) == 0 ->
 
196
            "&nbsp;";
 
197
        _ ->
 
198
            Str
 
199
    end.
 
200
 
 
201
 
 
202
mk_string(I) when integer(I) ->
 
203
    integer_to_list(I);
 
204
mk_string(A) when atom(A) ->
 
205
    atom_to_list(A);
 
206
mk_string(L) when list(L) ->
 
207
    %% again, we can't regognize a string without "parsing" it
 
208
    case catch list_to_binary(L) of
 
209
        {'EXIT',_} ->
 
210
            io_lib:format("~p", [L]);
 
211
        _ ->
 
212
            L
 
213
    end;
 
214
mk_string(Term) ->
 
215
    io_lib:format("~p", [Term]).
 
216
 
 
217
 
 
218
 
 
219
find_attribute(Name, Attrs) ->
 
220
    case lists:keysearch(Name, #xmlAttribute.name, Attrs) of
 
221
        {value, #xmlAttribute{value = V}} ->
 
222
            {value, V};
 
223
        false ->
 
224
            false
 
225
    end.