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

« back to all changes in this revision

Viewing changes to lib/xmerl/src/xmerl_sax_old_dom.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%-*-erlang-*-
 
2
%%--------------------------------------------------------------------
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2009. 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    : xmerl_sax_old_dom.erl
 
21
%% Description : 
 
22
%%
 
23
%% Created : 02 Oct 2008 
 
24
%%----------------------------------------------------------------------
 
25
-module(xmerl_sax_old_dom).
 
26
 
 
27
%%----------------------------------------------------------------------
 
28
%% Include files
 
29
%%----------------------------------------------------------------------
 
30
-include("xmerl_sax_old_dom.hrl").
 
31
 
 
32
%%----------------------------------------------------------------------
 
33
%% External exports
 
34
%%----------------------------------------------------------------------
 
35
-export([
 
36
         initial_state/0,
 
37
         get_dom/1,
 
38
         event/3
 
39
        ]).
 
40
 
 
41
%%----------------------------------------------------------------------
 
42
%% Internal exports
 
43
%%----------------------------------------------------------------------
 
44
-export([
 
45
        ]).
 
46
 
 
47
%%======================================================================
 
48
%% Macros
 
49
%%======================================================================
 
50
%%----------------------------------------------------------------------
 
51
%% Error handling
 
52
%%----------------------------------------------------------------------
 
53
-define(error(Reason), 
 
54
        throw({xmerl_sax_old_dom_error, Reason})).
 
55
 
 
56
%%======================================================================
 
57
%% Records
 
58
%%======================================================================
 
59
 
 
60
%%----------------------------------------------------------------------
 
61
%% State record for the validator
 
62
%%----------------------------------------------------------------------
 
63
-record(xmerl_sax_old_dom_state, {
 
64
          tags=[],         %% Tag stack
 
65
          cno=[],          %% Current node number
 
66
          namespaces = [], %% NameSpace stack
 
67
          dom=[]           %% DOM structure         
 
68
         }).
 
69
 
 
70
%%======================================================================
 
71
%% External functions
 
72
%%======================================================================
 
73
%%----------------------------------------------------------------------
 
74
%% Function: initial_state() -> Result
 
75
%% Parameters: 
 
76
%% Result: 
 
77
%% Description:
 
78
%%----------------------------------------------------------------------
 
79
initial_state() ->
 
80
    #xmerl_sax_old_dom_state{}.
 
81
 
 
82
%%----------------------------------------------------------------------
 
83
%% Function: get_dom(State) -> Result
 
84
%% Parameters: 
 
85
%% Result: 
 
86
%% Description:
 
87
%%----------------------------------------------------------------------
 
88
get_dom(#xmerl_sax_old_dom_state{dom=Dom}) ->
 
89
    Dom.
 
90
 
 
91
%%----------------------------------------------------------------------
 
92
%% Function: event(Event, LineNo, State) -> Result
 
93
%% Parameters: 
 
94
%% Result: 
 
95
%% Description:
 
96
%%----------------------------------------------------------------------
 
97
event(Event, _LineNo, State) ->
 
98
    build_dom(Event, State).
 
99
 
 
100
 
 
101
%%======================================================================
 
102
%% Internal functions
 
103
%%======================================================================
 
104
 
 
105
%%----------------------------------------------------------------------
 
106
%% Function  : build_dom(Event, State) -> Result
 
107
%% Parameters: Event = term()
 
108
%%             State = #xmerl_sax_old_dom_state{}
 
109
%% Result    : #xmerl_sax_old_dom_state{} |
 
110
%% Description: 
 
111
%%----------------------------------------------------------------------
 
112
 
 
113
%% Document
 
114
%%----------------------------------------------------------------------
 
115
build_dom(startDocument, State) ->
 
116
    State#xmerl_sax_old_dom_state{dom=[startDocument]};
 
117
build_dom(endDocument, 
 
118
          #xmerl_sax_old_dom_state{dom=[#xmlElement{content=C} = Current |D]} = State) ->
 
119
    case D of
 
120
        [startDocument] ->
 
121
            State#xmerl_sax_old_dom_state{dom=[Current#xmlElement{
 
122
                                                            content=lists:reverse(C)
 
123
                                                           }]};
 
124
        [#xmlDecl{} = Decl, startDocument] ->
 
125
            State#xmerl_sax_old_dom_state{dom=[Decl, Current#xmlElement{
 
126
                                                 content=lists:reverse(C)
 
127
                                                }]};
 
128
        _ ->
 
129
            io:format("~p\n", [D]),
 
130
            ?error("we're not at end the document when endDocument event is encountered.")
 
131
    end;
 
132
 
 
133
%% Element
 
134
%%----------------------------------------------------------------------
 
135
build_dom({startElement, Uri, LocalName, QName, Attributes}, 
 
136
          #xmerl_sax_old_dom_state{tags=T, cno=CN, namespaces=NS, dom=D} = State) ->
 
137
 
 
138
    A = parse_attributes(LocalName, Attributes),
 
139
    {Num, NewCN} =
 
140
        case CN of
 
141
            [] ->
 
142
                {1, [1]};
 
143
            [ N |CNs] ->
 
144
                {N, [1, N+1 |CNs]}
 
145
        end,
 
146
 
 
147
    NsInfo = 
 
148
        case QName of
 
149
            {[], _} -> [];
 
150
            QN -> QN
 
151
        end,
 
152
    NameAsAtom = convert_qname_to_atom(QName), 
 
153
 
 
154
    State#xmerl_sax_old_dom_state{tags=[{NameAsAtom, Num} |T],
 
155
                                  cno=NewCN,
 
156
                                  dom=[#xmlElement{name=NameAsAtom, 
 
157
                                                   expanded_name=NameAsAtom,
 
158
                                                   nsinfo=NsInfo,
 
159
                                                   namespace=#xmlNamespace{default=list_to_atom(Uri),
 
160
                                                                           nodes=NS},
 
161
                                                   pos=Num,
 
162
                                                   parents=T,
 
163
                                                   attributes=lists:reverse(A),
 
164
                                                   xmlbase="."
 
165
                                                  } | D]};
 
166
build_dom({endElement, _Uri, LocalName, QName}, 
 
167
          #xmerl_sax_old_dom_state{tags=[_ |T],
 
168
                                   cno=[_ |CN],
 
169
                                   dom=[#xmlElement{name=CName, content=C} = Current, 
 
170
                                        #xmlElement{content=PC} = Parent | D]} = State) ->
 
171
    case convert_qname_to_atom(QName) of
 
172
        CName ->            
 
173
            State#xmerl_sax_old_dom_state{tags=T,
 
174
                                          cno=CN,
 
175
                                          dom=[Parent#xmlElement{
 
176
                                                 content=[Current#xmlElement{
 
177
                                                            content=lists:reverse(C)
 
178
                                                           }
 
179
                                                          |PC]
 
180
                                                } | D]};
 
181
        _ ->
 
182
            ?error("Got end of element: " ++ LocalName ++ " but expected: " ++ 
 
183
                   Current#xmlElement.name)
 
184
    end;
 
185
 
 
186
%% Text 
 
187
%%----------------------------------------------------------------------
 
188
build_dom({characters, String},
 
189
          #xmerl_sax_old_dom_state{tags=T, 
 
190
                                   cno=[Num |CN],
 
191
                                   dom=[#xmlElement{content=C} = Current| D]} = State) ->
 
192
    State#xmerl_sax_old_dom_state{cno=[Num+1 |CN], 
 
193
                                  dom=[Current#xmlElement{content=[#xmlText{value=String, parents=T, pos=Num, type=text}
 
194
                                                                   |C]} | D]};
 
195
build_dom({ignorableWhitespace, String},
 
196
          #xmerl_sax_old_dom_state{tags=T, 
 
197
                                   cno=[Num |CN],
 
198
                                   dom=[#xmlElement{content=C} = Current| D]} = State) ->
 
199
    State#xmerl_sax_old_dom_state{cno=[Num+1 |CN],
 
200
                                  dom=[Current#xmlElement{content=[#xmlText{value=String, 
 
201
                                                                            parents=T, pos=Num, 
 
202
                                                                            type=text}
 
203
                                                                   |C]} | D]};
 
204
 
 
205
%% Comments
 
206
%%----------------------------------------------------------------------
 
207
build_dom({comment, String},
 
208
          #xmerl_sax_old_dom_state{tags=T, 
 
209
                                   cno=[Num |CN],
 
210
                                   dom=[#xmlElement{content=C} = Current| D]} = State) ->
 
211
    State#xmerl_sax_old_dom_state{cno=[Num+1 |CN],
 
212
                                  dom=[Current#xmlElement{content=[#xmlComment{parents=T, pos=Num, value=String}|C]} | D]};
 
213
 
 
214
%% NameSpaces
 
215
%%----------------------------------------------------------------------
 
216
build_dom({startPrefixMapping, [], _Uri}, State) -> 
 
217
    State;
 
218
build_dom({startPrefixMapping, Prefix, Uri},
 
219
          #xmerl_sax_old_dom_state{namespaces=NS} = State) -> 
 
220
    State#xmerl_sax_old_dom_state{namespaces=[{Prefix, list_to_atom(Uri)} |NS]};
 
221
build_dom({endPrefixMapping, Prefix},
 
222
          #xmerl_sax_old_dom_state{namespaces=[{Prefix, _} |NS]} = State) -> 
 
223
    State#xmerl_sax_old_dom_state{namespaces=NS};
 
224
 
 
225
%% Processing instructions
 
226
%%----------------------------------------------------------------------
 
227
build_dom({processingInstruction,"xml", PiData},
 
228
          #xmerl_sax_old_dom_state{dom=D} = State) ->
 
229
    {Vsn, PiData1}  = find_and_remove_attribute("version", PiData, []),
 
230
    {Enc, PiData2}  = find_and_remove_attribute("encoding", PiData1, []),
 
231
    {Standalone, PiData3}  = find_and_remove_attribute("standalone", PiData2, yes),
 
232
    State#xmerl_sax_old_dom_state{dom=[#xmlDecl{vsn=Vsn, encoding=Enc, standalone=Standalone, attributes=PiData3}| D]};
 
233
build_dom({processingInstruction, PiTarget, PiData},
 
234
          #xmerl_sax_old_dom_state{cno=[Num |CN],
 
235
                                   dom=[#xmlElement{content=C} = Current| D]} = State) ->
 
236
    State#xmerl_sax_old_dom_state{cno=[Num+1 |CN], 
 
237
                                  dom=[Current#xmlElement{content=[#xmlPI{name=PiTarget,pos=Num, value=PiData}
 
238
                                                                   |C]} | D]};
 
239
%% Default
 
240
%%----------------------------------------------------------------------
 
241
build_dom(_E, State) ->
 
242
    State. 
 
243
 
 
244
 
 
245
%%----------------------------------------------------------------------
 
246
%% Function  : parse_attributes(ElName, Attributes) -> Result
 
247
%% Parameters: 
 
248
%% Result    : 
 
249
%% Description: 
 
250
%%----------------------------------------------------------------------
 
251
parse_attributes(ElName, Attributes) ->
 
252
    parse_attributes(ElName, Attributes, 1, []).
 
253
 
 
254
parse_attributes(_, [], _, Acc) ->
 
255
    Acc;
 
256
parse_attributes(ElName, [{_Uri, Prefix, LocalName, AttrValue} |As], N, Acc) ->  
 
257
    Name = convert_qname_to_atom({Prefix,LocalName}),
 
258
    NsInfo = 
 
259
        case Prefix of
 
260
            [] -> [];
 
261
            P -> {P,LocalName}
 
262
        end,
 
263
    parse_attributes(ElName, As, N+1, [#xmlAttribute{name=Name,
 
264
                                                     pos=N, 
 
265
                                                     nsinfo=NsInfo,
 
266
                                                     value=AttrValue,
 
267
                                                     normalized=false} |Acc]).
 
268
 
 
269
%%----------------------------------------------------------------------
 
270
%% Function  : convert_qname_to_atom(QName) -> Result
 
271
%% Parameters: 
 
272
%% Result    : 
 
273
%% Description: 
 
274
%%----------------------------------------------------------------------
 
275
convert_qname_to_atom({[], N}) ->
 
276
    list_to_atom(N);
 
277
convert_qname_to_atom({P,N}) ->
 
278
    list_to_atom(P ++ ":" ++ N).
 
279
 
 
280
%%----------------------------------------------------------------------
 
281
%% Function  : find_and_remove_attribute(Key, Data, Default) -> Result
 
282
%% Parameters: 
 
283
%% Result    : 
 
284
%% Description: 
 
285
%%----------------------------------------------------------------------
 
286
find_and_remove_attribute(Key, Data, Default) ->
 
287
    case lists:keysearch(Key, 1, Data) of
 
288
        {value, {Key, Value}} ->
 
289
            Data2 = lists:keydelete(Key, 1, Data),
 
290
            {Value, Data2};
 
291
        false ->
 
292
            {Default, Data}
 
293
    end.