~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
56
56
    ">" ++ export_text(T, Cont);
57
57
export_text([$& | T], Cont) ->
58
58
    "&" ++ export_text(T, Cont);
59
 
export_text([C | T], Cont) when integer(C) ->
 
59
export_text([C | T], Cont) when is_integer(C) ->
60
60
    [C | export_text(T, Cont)];
61
61
export_text([T | T1], Cont) ->
62
62
    export_text(T, [T1 | Cont]);
73
73
flatten_text(T) ->
74
74
    flatten_text(T, []).
75
75
 
76
 
flatten_text([C | T], Cont) when integer(C) ->
 
76
flatten_text([C | T], Cont) when is_integer(C) ->
77
77
    [C | flatten_text(T, Cont)];
78
78
flatten_text([T | T1], Cont) ->
79
79
    flatten_text(T, [T1 | Cont]);
89
89
%% markup-generating functions (`start_tag', `end_tag', ...) always use
90
90
%% `"' to delimit the attribute values.)
91
91
 
92
 
export_attribute(I) when integer(I) ->
 
92
export_attribute(I) when is_integer(I) ->
93
93
    integer_to_list(I);
94
 
export_attribute(A) when atom(A) ->
 
94
export_attribute(A) when is_atom(A) ->
95
95
    export_attribute(atom_to_list(A), []);
96
96
export_attribute(S) ->
97
97
    export_attribute(S, []).
102
102
    "&" ++ export_attribute(T, Cont);
103
103
export_attribute([$" | T], Cont) ->
104
104
    """ ++ export_attribute(T, Cont);
105
 
export_attribute([C | T], Cont) when integer(C) ->
 
105
export_attribute([C | T], Cont) when is_integer(C) ->
106
106
    [C | export_attribute(T, Cont)];
107
107
export_attribute([T | T1], Cont) ->
108
108
    export_attribute(T, [T1 | Cont]);
169
169
expand_element(E = #xmlDecl{}, _Pos, _Parents, _Norm) ->
170
170
    Attrs = expand_attributes(E#xmlDecl.attributes, 1, []),
171
171
    E#xmlDecl{attributes = Attrs};
172
 
expand_element({Tag, Attrs, Content}, Pos, Parents, Norm) when atom(Tag) ->
 
172
expand_element({Tag, Attrs, Content}, Pos, Parents, Norm) when is_atom(Tag) ->
173
173
    NewParents = [{Tag, Pos} | Parents],
174
174
    #xmlElement{name = Tag,
175
175
                pos = Pos,
176
176
                parents = Parents,
177
177
                attributes = expand_attributes(Attrs, 1, NewParents),
178
178
                content = expand_content(Content, 1, NewParents, Norm)};
179
 
expand_element({Tag, Content}, Pos, Parents, Norm) when atom(Tag) ->
 
179
expand_element({Tag, Content}, Pos, Parents, Norm) when is_atom(Tag) ->
180
180
    NewParents = [{Tag, Pos} | Parents],
181
181
    #xmlElement{name = Tag,
182
182
                pos = Pos,
183
183
                parents = Parents,
184
184
                attributes = [],
185
185
                content = expand_content(Content, 1, NewParents, Norm)};
186
 
expand_element(Tag, Pos, Parents, _Norm) when atom(Tag) ->
 
186
expand_element(Tag, Pos, Parents, _Norm) when is_atom(Tag) ->
187
187
    #xmlElement{name = Tag,
188
188
                pos = Pos,
189
189
                parents = Parents,
190
190
                attributes = [],
191
191
                content = []};
192
 
expand_element(String, Pos, Parents, Norm) when list(String) ->
 
192
expand_element(String, Pos, Parents, Norm) when is_list(String) ->
193
193
    #xmlText{pos = Pos,
194
194
             parents = Parents,
195
195
             value = expand_text(String, Norm)}.
269
269
    {Name, simplify_attributes(Attrs), simplify_content(Content)};
270
270
simplify_element(#xmlText{value = Text}) ->
271
271
    Text;
272
 
simplify_element({Tag, Attrs, Content}) when atom(Tag) ->
 
272
simplify_element({Tag, Attrs, Content}) when is_atom(Tag) ->
273
273
    {Tag, simplify_attributes(Attrs), simplify_content(Content)};
274
 
simplify_element({Tag, Content}) when atom(Tag) ->
 
274
simplify_element({Tag, Content}) when is_atom(Tag) ->
275
275
    {Tag, [], simplify_content(Content)};
276
 
simplify_element(Tag) when atom(Tag) ->
 
276
simplify_element(Tag) when is_atom(Tag) ->
277
277
    {Tag, [], []};
278
 
simplify_element(Text) when list(Text) ->
 
278
simplify_element(Text) when is_list(Text) ->
279
279
    Text.
280
280
 
281
281
simplify_content([#xmlPI{} | T]) ->
290
290
    [].
291
291
 
292
292
simplify_attributes([#xmlAttribute{name = K, value = V} | T])
293
 
  when atom(K) ->
 
293
  when is_atom(K) ->
294
294
    [{K, expand_value(V)} | simplify_attributes(T)];
295
 
simplify_attributes([H = {K, _} | T]) when atom(K) ->
 
295
simplify_attributes([H = {K, _} | T]) when is_atom(K) ->
296
296
    [H | simplify_attributes(T)];
297
297
simplify_attributes([]) ->
298
298
    [].
319
319
start_tag(TagStr) ->
320
320
    start_tag(TagStr, []).
321
321
 
322
 
start_tag(Tag, Attrs) when atom(Tag) ->
 
322
start_tag(Tag, Attrs) when is_atom(Tag) ->
323
323
    start_tag(atom_to_list(Tag), Attrs);
324
324
start_tag(TagStr, []) ->
325
325
    ["<", TagStr, ">"];
329
329
empty_tag(Tag) ->
330
330
    empty_tag(Tag, []).
331
331
 
332
 
empty_tag(Tag, Attrs) when atom(Tag) ->
 
332
empty_tag(Tag, Attrs) when is_atom(Tag) ->
333
333
    empty_tag(atom_to_list(Tag), Attrs);
334
334
empty_tag(TagStr, []) ->
335
335
    ["<", TagStr, "/>"];
336
336
empty_tag(TagStr, Attrs) ->
337
337
    ["<", TagStr, attributes(Attrs), "/>"].
338
338
 
339
 
end_tag(Tag) when atom(Tag) ->
 
339
end_tag(Tag) when is_atom(Tag) ->
340
340
    end_tag(atom_to_list(Tag));
341
341
end_tag(TagStr) ->
342
342
    ["</", TagStr, ">"].
382
382
    C1 = Fun(E),
383
383
    C2 = mapxml(Fun,lists:flatten(C1#xmlElement.content)),
384
384
    C1#xmlElement{content=C2};
385
 
mapxml(Fun, List) when list(List) ->
 
385
mapxml(Fun, List) when is_list(List) ->
386
386
    AFun = fun(E) -> mapxml(Fun, E) end,
387
387
    lists:map(AFun, List);
388
388
mapxml(Fun, E) ->
394
394
foldxml(Fun, Accu0, #xmlElement{content=C}=E) ->
395
395
    Accu1 = Fun(E, Accu0),
396
396
    foldxml(Fun, Accu1, C);
397
 
foldxml(Fun, Accu, List) when list(List) ->
 
397
foldxml(Fun, Accu, List) when is_list(List) ->
398
398
    AFun = fun(E,A) -> foldxml(Fun, A, E) end,
399
399
    lists:foldl(AFun, Accu, List);
400
400
foldxml(Fun, Accu, E) ->
407
407
    {C1,Accu1} = Fun(E, Accu0),
408
408
    {C2,Accu2} = mapfoldxml(Fun, Accu1, lists:flatten(C1#xmlElement.content)),
409
409
    {C1#xmlElement{content=C2},Accu2};
410
 
mapfoldxml(Fun, Accu, List) when list(List) ->
 
410
mapfoldxml(Fun, Accu, List) when is_list(List) ->
411
411
    AFun = fun(E,A) -> mapfoldxml(Fun, A, E) end,
412
412
    lists:mapfoldl(AFun, Accu, List);
413
413
mapfoldxml(Fun, Accu, E) ->
432
432
%%%   ExtCharset is any externally declared character set (e.g. in HTTP
433
433
%%%   Content-Type header) and Content is an XML Document.
434
434
%%% 
435
 
detect_charset(ExtCharset,Content) when list(ExtCharset) ->
 
435
detect_charset(ExtCharset,Content) when is_list(ExtCharset) ->
436
436
    %% FIXME! Don't allow both atom and list for character set names
437
437
    detect_charset(list_to_atom(ExtCharset),Content);
438
438
detect_charset(ExtCharset,Content) ->
513
513
    {ExtCharset, Content}.
514
514
 
515
515
 
516
 
is_ncname(A) when atom(A) ->
 
516
is_ncname(A) when is_atom(A) ->
517
517
    is_ncname(atom_to_list(A));
518
518
is_ncname([$_|T]) ->
519
519
    is_name1(T);
524
524
        _ -> false
525
525
    end.
526
526
 
527
 
is_name(A) when atom(A) ->
 
527
is_name(A) when is_atom(A) ->
528
528
    is_name(atom_to_list(A));
529
529
is_name([$_|T]) ->
530
530
    is_name1(T);