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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

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.6
 
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
%%% @private
 
23
%%% File:       xmerl_xpath_pred.erl
 
24
%%% Author       : Ulf Wiger <ulf.wiger@ericsson.com>
 
25
%%% Description  : Helper module to xmerl_xpath: XPATH predicates.
 
26
%%% 
 
27
%%% Modules used : lists, string, xmerl_scan, xmerl_xpath
 
28
%%% 
 
29
%%%----------------------------------------------------------------------
 
30
 
 
31
-module(xmerl_xpath_pred).
 
32
-vsn('0.6').
 
33
-date('00-09-22').
 
34
-author('ulf.wiger@ericsson.com').
 
35
 
 
36
%% API
 
37
-export([eval/2]).
 
38
 
 
39
 
 
40
%% internal functions (called via apply/3)
 
41
-export([boolean/1, boolean/2,
 
42
         ceiling/2,
 
43
         concat/2,
 
44
         contains/2,
 
45
         count/2,
 
46
         floor/2,
 
47
         fn_false/2,
 
48
         fn_not/2,
 
49
         fn_true/2,
 
50
         id/2,
 
51
         lang/2,
 
52
         last/2,
 
53
         'local-name'/2,
 
54
         'namespace-uri'/2,
 
55
         nodeset/1,
 
56
         'normalize-space'/2,
 
57
         number/1, number/2,
 
58
         position/2,
 
59
         round/2,
 
60
         'starts-with'/2,
 
61
         string/1,
 
62
         'string-length'/2,
 
63
         substring/2,
 
64
         'substring-after'/2,
 
65
         'substring-before'/2,
 
66
         sum/2,
 
67
         translate/2]).
 
68
         
 
69
 
 
70
-include("xmerl.hrl").
 
71
-include("xmerl_xpath.hrl").
 
72
 
 
73
%% -record(obj, {type,
 
74
%%            value}).
 
75
 
 
76
 
 
77
-define(string(X), #xmlObj{type = string,
 
78
                           value = X}).
 
79
-define(nodeset(X), #xmlObj{type = nodeset,
 
80
                            value = X}).
 
81
-define(number(X), #xmlObj{type = number,
 
82
                           value = X}).
 
83
-define(boolean(X), #xmlObj{type = boolean,
 
84
                            value = X}).
 
85
 
 
86
 
 
87
 
 
88
 
 
89
eval(Expr, C = #xmlContext{context_node = #xmlNode{pos = Pos}}) ->
 
90
    Obj = expr(Expr, C),
 
91
    Res = case Obj#xmlObj.type of
 
92
              number when Obj#xmlObj.value == Pos ->
 
93
                  true;
 
94
              number ->
 
95
                  false;
 
96
              boolean ->
 
97
                  Obj#xmlObj.value;
 
98
              _ ->
 
99
                  mk_boolean(C, Obj)
 
100
          end,
 
101
%    io:format("eval(~p, ~p) -> ~p~n", [Expr, Pos, Res]),
 
102
    Res.
 
103
 
 
104
 
 
105
string(X) ->
 
106
    ?string(X).
 
107
 
 
108
nodeset(X) -> 
 
109
    ?nodeset(X).
 
110
 
 
111
number(X) ->
 
112
    ?number(X).
 
113
 
 
114
boolean(X) ->
 
115
    ?boolean(X).
 
116
 
 
117
 
 
118
expr({arith, Op, E1, E2}, C) ->
 
119
    arith_expr(Op, E1, E2, C);
 
120
expr({comp, Op, E1, E2}, C) ->
 
121
    comp_expr(Op, E1, E2, C);
 
122
expr({bool, Op, E1, E2}, C) ->
 
123
    bool_expr(Op, E1, E2, C);
 
124
expr({'negative', E}, C) ->
 
125
    N = mk_number(C, E),
 
126
    - N;
 
127
expr({number, N}, _C) ->
 
128
    ?number(N);
 
129
expr({literal, S}, _C) ->
 
130
    ?string(S);
 
131
expr({function_call, F, Args}, C) ->
 
132
    case core_function(F) of
 
133
        {true, F1} ->
 
134
            ?MODULE:F1(C, Args);
 
135
        true ->
 
136
            ?MODULE:F(C, Args);
 
137
        false ->
 
138
            %% here, we should look up the function in the context provided 
 
139
            %% by the caller, but we haven't figured this out yet.
 
140
            exit({not_a_core_function, F})
 
141
    end;
 
142
expr({path, Type, PathExpr}, C) ->
 
143
    #state{context=#xmlContext{nodeset = NS}} =
 
144
        xmerl_xpath:eval_path(Type, PathExpr, C),
 
145
    ?nodeset(NS);
 
146
expr(Expr, _C) ->
 
147
    exit({unknown_expr, Expr}).
 
148
 
 
149
 
 
150
arith_expr('+', E1, E2, C) ->
 
151
    ?number(mk_number(C, E1) + mk_number(C, E2));
 
152
arith_expr('-', E1, E2, C) ->
 
153
    ?number(mk_number(C, E1) - mk_number(C, E2));
 
154
arith_expr('*', E1, E2, C) ->
 
155
    ?number(mk_number(C, E1) * mk_number(C, E2));
 
156
arith_expr('div', E1, E2, C) ->
 
157
    ?number(mk_number(C, E1) / mk_number(C, E2));
 
158
arith_expr('mod', E1, E2, C) ->
 
159
    ?number(mk_number(C, E1) rem mk_number(C, E2)).
 
160
 
 
161
comp_expr('>', E1, E2, C) ->
 
162
    N1 = expr(E1,C),
 
163
    N2 = expr(E2,C),
 
164
    ?boolean(compare_ineq_format(N1,N2,C) > compare_ineq_format(N2,N1,C));
 
165
comp_expr('<', E1, E2, C) ->
 
166
    N1 = expr(E1,C),
 
167
    N2 = expr(E2,C),
 
168
    ?boolean(compare_ineq_format(N1,N2,C) > compare_ineq_format(N2,N1,C));
 
169
comp_expr('>=', E1, E2, C) ->
 
170
    N1 = expr(E1,C),
 
171
    N2 = expr(E2,C),
 
172
    ?boolean(compare_ineq_format(N1,N2,C) > compare_ineq_format(N2,N1,C));
 
173
comp_expr('<=', E1, E2, C) ->
 
174
    N1 = expr(E1,C),
 
175
    N2 = expr(E2,C),
 
176
    ?boolean(compare_ineq_format(N1,N2,C) > compare_ineq_format(N2,N1,C));
 
177
comp_expr('=', E1, E2, C) ->
 
178
    N1 = expr(E1,C),
 
179
    N2 = expr(E2,C),
 
180
    ?boolean(compare_eq_format(N1,N2,C) == compare_eq_format(N2,N1,C));
 
181
comp_expr('!=', E1, E2, C) ->
 
182
    N1 = expr(E1,C),
 
183
    N2 = expr(E2,C),
 
184
    ?boolean(compare_eq_format(N1,N2,C) == compare_eq_format(N2,N1,C)).
 
185
 
 
186
bool_expr('or', E1, E2, C) ->
 
187
    ?boolean(mk_boolean(C, E1) or mk_boolean(C, E2));
 
188
bool_expr('and', E1, E2, C) ->
 
189
    ?boolean(mk_boolean(C, E1) and mk_boolean(C, E2)).
 
190
 
 
191
%% According to chapter 3.4 in XML Path Language ver 1.0 the format of
 
192
%% the compared objects are depending on the type of the other
 
193
%% object. 
 
194
%% 1. Comparisons involving node-sets is treated equally despite
 
195
%% of which comparancy operand is used. In this case:
 
196
%% - node-set comp node-set: string values are used
 
197
%% - node-set comp number : ((node-set string value) -> number) 
 
198
%% - node-set comp boolean : (node-set string value) -> boolean
 
199
%% 2. Comparisons when neither object is a node-set and the operand
 
200
%% is = or != the following transformation is done before comparison:
 
201
%% - if one object is a boolean the other is converted to a boolean.
 
202
%% - if one object is a number the other is converted to a number.
 
203
%% - otherwise convert both to the string value.
 
204
%% 3. Comparisons when neither object is a node-set and the operand is
 
205
%% <=, <, >= or > both objects are converted to a number.
 
206
compare_eq_format(N1=#xmlObj{type=T1},N2=#xmlObj{type=T2},C) when T1==nodeset;
 
207
                                                              T2==nodeset ->
 
208
    compare_nseq_format(N1,N2,C);
 
209
compare_eq_format(N1=#xmlObj{type=T1},#xmlObj{type=T2},C) when T1==boolean;
 
210
                                                              T2==boolean ->
 
211
    mk_boolean(C,N1);
 
212
compare_eq_format(N1=#xmlObj{type=T1},#xmlObj{type=T2},C) when T1==number;
 
213
                                                              T2==number ->
 
214
    mk_number(C,N1);
 
215
compare_eq_format(N1,_,C) ->
 
216
    mk_string(C,string_value(N1)).
 
217
 
 
218
compare_ineq_format(N1=#xmlObj{type=T1},
 
219
                    N2=#xmlObj{type=T2},C) when T1==nodeset;
 
220
                                                T2==nodeset ->
 
221
    compare_nseq_format(N1,N2,C);
 
222
compare_ineq_format(N1,_N2,C) ->
 
223
    mk_number(C,N1).
 
224
 
 
225
compare_nseq_format(N1=#xmlObj{type = number},_N2,C) ->
 
226
    mk_number(C,N1);
 
227
compare_nseq_format(N1=#xmlObj{type = boolean},_N2,C) ->
 
228
    mk_boolean(C,N1);
 
229
compare_nseq_format(N1=#xmlObj{type = string},_N2,C) ->
 
230
    mk_string(C,N1);
 
231
compare_nseq_format(N1=#xmlObj{type = nodeset},_N2=#xmlObj{type=number},C) ->
 
232
    %% transform nodeset value to its string-value
 
233
    mk_number(C,string_value(N1));
 
234
compare_nseq_format(N1=#xmlObj{type = nodeset},_N2=#xmlObj{type=boolean},C) ->
 
235
    mk_boolean(C,N1);
 
236
compare_nseq_format(N1=#xmlObj{type = nodeset},_N2,C) ->
 
237
    mk_string(C,string_value(N1)).
 
238
 
 
239
 
 
240
core_function('last') ->                true;
 
241
core_function('position') ->            true;
 
242
core_function('count') ->               true;
 
243
core_function('id') ->                  true;
 
244
core_function('local-name') ->          true;
 
245
core_function('namespace-uri') ->       true;
 
246
core_function('name') ->                true;
 
247
core_function('string') ->              true;
 
248
core_function('concat') ->              true;
 
249
core_function('starts-with') ->         true;
 
250
core_function('contains') ->            true;
 
251
core_function('substring-before') ->    true;
 
252
core_function('substring-after') ->     true;
 
253
core_function('string-length') ->       true;
 
254
core_function('normalize-space') ->     true;
 
255
core_function('translate') ->           true;
 
256
core_function('boolean') ->             true;
 
257
core_function('not') ->                 {true, fn_not};
 
258
core_function('true') ->                {true, fn_true};
 
259
core_function('false') ->               {true, fn_false};
 
260
core_function('lang') ->                true;
 
261
core_function('number') ->              true;
 
262
core_function('sum') ->                 true;
 
263
core_function('floor') ->               true;
 
264
core_function('ceiling') ->             true;
 
265
core_function('round') ->               true;
 
266
core_function(_) ->
 
267
    false.
 
268
 
 
269
 
 
270
%%%  node set functions
 
271
 
 
272
%% number: last()
 
273
last(#xmlContext{nodeset = Set}, []) ->
 
274
    ?number(length(Set)).
 
275
 
 
276
%% number: position()
 
277
position(#xmlContext{context_node = #xmlNode{pos = Pos}}, []) ->
 
278
    ?number(Pos).
 
279
 
 
280
%% number: count(node-set)
 
281
count(C, [Arg]) ->
 
282
    ?number(length(mk_nodeset(C, Arg))).
 
283
 
 
284
%% node-set: id(object)
 
285
id(C, [Arg]) ->
 
286
    NS0 = [C#xmlContext.whole_document],
 
287
    case Arg#xmlObj.type of
 
288
        nodeset ->
 
289
            NodeSet = Arg#xmlObj.value,
 
290
            IdTokens = 
 
291
                lists:foldl(
 
292
                  fun(N, AccX) ->
 
293
                          StrVal = string_value(N),
 
294
                          TokensX = id_tokens(StrVal),
 
295
                          TokensX ++ AccX
 
296
                  end, [], NodeSet),
 
297
            NewNodeSet = 
 
298
                xmerl_xpath:axis(descendant_or_self, 
 
299
                                 fun(Node) ->
 
300
                                         attribute_test(Node, id, IdTokens)
 
301
                                 end, C#xmlContext{nodeset = NS0}),
 
302
            ?nodeset(NewNodeSet);
 
303
        _ ->
 
304
            StrVal = string_value(Arg#xmlObj.value),
 
305
            IdTokens = id_tokens(StrVal),
 
306
            lists:foldl(
 
307
              fun(Tok, AccX) ->
 
308
                      select_on_attribute(NS0, id, Tok, AccX)
 
309
              end, [], IdTokens)
 
310
    end.
 
311
 
 
312
id_tokens(Str) ->
 
313
    string:tokens(Str, " \t\n\r").
 
314
                          
 
315
 
 
316
attribute_test(#xmlNode{node = #xmlElement{attributes = Attrs}}, 
 
317
               Key, Vals) ->
 
318
    case lists:keysearch(Key, #xmlAttribute.name, Attrs) of
 
319
        {value, #xmlAttribute{value = V}} ->
 
320
            lists:member(V, Vals);
 
321
        _ ->
 
322
            false
 
323
    end;
 
324
attribute_test(_Node, _Key, _Vals) ->
 
325
    false.
 
326
 
 
327
%%% CONTINUE HERE!!!!
 
328
 
 
329
%% string: local-name(node-set?)
 
330
'local-name'(C, []) ->
 
331
    local_name1(default_nodeset(C));
 
332
 
 
333
'local-name'(C, [Arg]) ->
 
334
    local_name1(mk_nodeset(C, Arg)).
 
335
 
 
336
local_name1([]) ->
 
337
    ?string([]);
 
338
local_name1([#xmlElement{name = Name, nsinfo = NSI}|_]) ->
 
339
    case NSI of
 
340
        {_Prefix, Local} ->
 
341
            ?string(Local);
 
342
        [] ->
 
343
            ?string(Name)
 
344
    end.
 
345
 
 
346
%% string: namespace-uri(node-set?)
 
347
'namespace-uri'(C, []) ->
 
348
    ns_uri(default_nodeset(C));
 
349
 
 
350
'namespace-uri'(C, [Arg]) ->
 
351
    ns_uri(mk_nodeset(C, Arg)).
 
352
 
 
353
 
 
354
ns_uri([]) ->
 
355
    ?string([]);
 
356
ns_uri([#xmlElement{nsinfo = NSI, namespace = NS}|_]) ->
 
357
    case NSI of
 
358
        {Prefix, _} ->
 
359
            case lists:keysearch(Prefix, 1, NS#xmlNamespace.nodes) of
 
360
                false ->
 
361
                    ?string([]);
 
362
                {value, {_K, V}} ->
 
363
                    ?string(V)
 
364
            end;
 
365
        [] ->
 
366
            []
 
367
    end.
 
368
 
 
369
 
 
370
 
 
371
%%% String functions
 
372
 
 
373
%% string: string(object?)
 
374
string(C, []) ->
 
375
    ns_string(default_nodeset(C));
 
376
string(C, [Arg]) ->
 
377
    string_value(mk_object(C, Arg)).
 
378
 
 
379
ns_string([Obj|_]) ->
 
380
    string_value(Obj).
 
381
 
 
382
string_value(#xmlObj{type=nodeset,value=[]}) ->
 
383
    ?string("");
 
384
string_value(N=#xmlObj{type=nodeset}) ->
 
385
    string_value(hd(N#xmlObj.value));
 
386
string_value(N=#xmlObj{}) ->
 
387
    string_value(N#xmlObj.value);
 
388
%% Needed also string_value for root_nodes, elements (concatenation of
 
389
%% al decsendant text nodes) and attribute nodes (normalized value).
 
390
string_value(A=#xmlNode{type=attribute}) ->
 
391
    #xmlAttribute{value=AttVal}=A#xmlNode.node,
 
392
    ?string(AttVal);
 
393
string_value(El=#xmlNode{type=element}) ->
 
394
    #xmlElement{content=C} = El#xmlNode.node,
 
395
    TextValue = fun(#xmlText{value=T},_Fun) -> T;
 
396
                        (#xmlElement{content=Cont},Fun) -> Fun(Cont,Fun);
 
397
                        (_,_) -> []
 
398
                     end,
 
399
    TextDecendants=fun(X) -> TextValue(X,TextValue) end,
 
400
    ?string(lists:flatten(lists:map(TextDecendants,C)));
 
401
string_value(infinity) -> ?string("Infinity");
 
402
string_value(neg_infinity) -> ?string("-Infinity");
 
403
string_value(A) when atom(A) ->
 
404
    ?string(atom_to_list(A));
 
405
string_value(N) when integer(N) ->
 
406
    ?string(integer_to_list(N));
 
407
string_value(N) when float(N) ->
 
408
    N1 = round(N * 10000000000000000),
 
409
    ?string(strip_zeroes(integer_to_list(N1))).
 
410
 
 
411
strip_zeroes(Str) ->
 
412
    strip_zs(lists:reverse(Str), 15).
 
413
 
 
414
strip_zs([H|T], 0) ->
 
415
    lists:reverse(T) ++ [$., H];
 
416
strip_zs("0" ++ T, N) ->
 
417
    strip_zs(T, N-1);
 
418
strip_zs([H|T], N) ->
 
419
    strip_zs(T, N-1, [H]).
 
420
 
 
421
strip_zs([H|T], 0, Acc) ->
 
422
    lists:reverse(T) ++ [$.,H|Acc];
 
423
strip_zs([H|T], N, Acc) ->
 
424
    strip_zs(T, N-1, [H|Acc]).
 
425
 
 
426
 
 
427
%% string: concat(string, string, string*)
 
428
concat(C, Args = [_, _|_]) ->
 
429
    Strings = [mk_string(C, A) || A <- Args],
 
430
    ?string(lists:concat(Strings)).
 
431
 
 
432
%% boolean: starts-with(string, string)
 
433
'starts-with'(C, [A1, A2]) ->
 
434
    ?boolean(lists:prefix(mk_string(C, A1), mk_string(C, A2))).
 
435
 
 
436
%% boolean: contains(string, string)
 
437
contains(C, [A1, A2]) ->
 
438
    Pos = string:str(mk_string(C, A1), mk_string(C, A2)),
 
439
    ?boolean(Pos > 0).
 
440
 
 
441
%% string: substring-before(string, string)
 
442
'substring-before'(C, [A1, A2]) ->
 
443
    S1 = mk_string(C, A1),
 
444
    S2 = mk_string(C, A2),
 
445
    Pos = string:str(S1, S2),
 
446
    ?string(string:substr(S1, 1, Pos)).
 
447
 
 
448
%% string: substring-after(string, string)
 
449
'substring-after'(C, [A1, A2]) ->
 
450
    S1 = mk_string(C, A1),
 
451
    S2 = mk_string(C, A2),
 
452
    case string:str(S1, S2) of
 
453
        0 ->
 
454
            ?string([]);
 
455
        Pos ->
 
456
            ?string(string:substr(S1, Pos))
 
457
    end.
 
458
 
 
459
%% string: substring(string, number, number?)
 
460
substring(C, [A1, A2]) ->
 
461
    S = mk_string(C, A1),
 
462
    Pos = mk_integer(C, A2),
 
463
    ?string(string:substr(S, Pos));
 
464
substring(C, [A1, A2, A3]) ->
 
465
    S = mk_string(C, A1),
 
466
    Pos = mk_integer(C, A2),
 
467
    Length = mk_integer(C, A3),
 
468
    ?string(string:substr(S, Pos, Length)).
 
469
 
 
470
 
 
471
%% number: string-length(string?)
 
472
'string-length'(C = #xmlContext{context_node = N}, []) ->
 
473
    length(mk_string(C, string_value(N)));
 
474
 
 
475
'string-length'(C, [A]) ->
 
476
    length(mk_string(C, A)).
 
477
 
 
478
 
 
479
%% string: normalize-space(string?)
 
480
'normalize-space'(C = #xmlContext{context_node = N}, []) ->
 
481
    normalize(mk_string(C, string_value(N)));
 
482
 
 
483
'normalize-space'(C, [A]) ->
 
484
    normalize(mk_string(C, A)).
 
485
 
 
486
 
 
487
%% string: translate(string, string, string)
 
488
translate(C, [A1, A2, A3]) ->
 
489
    S1 = mk_string(C, A1),
 
490
    S2 = mk_string(C, A2),
 
491
    S3 = mk_string(C, A3),
 
492
    ?string(translate1(S1, translations(S2, S3))).
 
493
 
 
494
translate1([H|T], Xls) ->
 
495
    case lists:keysearch(H, 1, Xls) of
 
496
        {value, {_, remove}} ->
 
497
            translate1(T, Xls);
 
498
        {value, {_, replace, H1}} ->
 
499
            [H1|translate1(T, Xls)];
 
500
        false ->
 
501
            [H|translate1(T, Xls)]
 
502
    end;
 
503
translate1([], _) ->
 
504
    [].
 
505
 
 
506
translations([H|T], [H1|T1]) ->
 
507
    [{H, replace, H1}|translations(T, T1)];
 
508
translations(Rest, []) ->
 
509
    [{X, remove} || X <- Rest];
 
510
translations([], _Rest) ->
 
511
    [].
 
512
 
 
513
 
 
514
 
 
515
%% boolean: boolean(object)
 
516
boolean(C, [Arg]) ->
 
517
    ?boolean(mk_boolean(C, Arg)).
 
518
 
 
519
%% boolean: not(boolean) ->
 
520
fn_not(C, [Arg]) ->
 
521
    ?boolean(not(mk_boolean(C, Arg))).
 
522
 
 
523
%% boolean: true() ->
 
524
fn_true(_C, []) ->
 
525
    ?boolean(true).
 
526
 
 
527
%% boolean: false() ->
 
528
fn_false(_C, []) ->
 
529
    ?boolean(false).
 
530
 
 
531
%% boolean: lang(string) ->
 
532
lang(C = #xmlContext{context_node = N}, [Arg]) ->
 
533
    S = mk_string(C, Arg),
 
534
    Lang = 
 
535
        case N of
 
536
            #xmlElement{language = L} -> L;
 
537
            #xmlAttribute{language = L} -> L;
 
538
            #xmlText{language = L} -> L;
 
539
            #xmlComment{language = L} -> L;
 
540
            _ -> []
 
541
        end,
 
542
    case Lang of
 
543
        [] ->
 
544
            ?boolean(false);
 
545
        _ ->
 
546
            ?boolean(match_lang(upcase(S), upcase(Lang)))
 
547
    end.
 
548
 
 
549
 
 
550
upcase([H|T]) when H >= $a, H =< $z ->
 
551
    [H+($A-$a)|upcase(T)];
 
552
upcase([H|T]) ->
 
553
    [H|upcase(T)];
 
554
upcase([]) ->
 
555
    [].
 
556
 
 
557
match_lang([H|T], [H|T1]) ->
 
558
    match_lang(T, T1);
 
559
match_lang([], "-" ++ _) ->
 
560
    true;
 
561
match_lang([], []) ->
 
562
    true;
 
563
match_lang(_, _) ->
 
564
    false.
 
565
        
 
566
 
 
567
 
 
568
%% number: number(object)
 
569
number(C = #xmlContext{context_node = N}, []) ->
 
570
    ?number(mk_number(C, string(C, N)));
 
571
number(C, [Arg]) ->
 
572
    ?number(mk_number(C, Arg)).
 
573
 
 
574
 
 
575
sum(C, [Arg]) ->
 
576
    NS = mk_nodeset(C, Arg),
 
577
    lists:foldl(
 
578
      fun(N, Sum) ->
 
579
              Sum + mk_number(C, string(C, N))
 
580
      end, 0, NS).
 
581
 
 
582
floor(C, [Arg]) ->
 
583
    Num = mk_number(C, Arg),
 
584
    case trunc(Num) of
 
585
        Num1 when Num1 > Num ->
 
586
            ?number(Num1-1);
 
587
        Num1 ->
 
588
            ?number(Num1)
 
589
    end.
 
590
 
 
591
ceiling(C, [Arg]) ->
 
592
    Num = mk_number(C, Arg),
 
593
    case trunc(Num) of
 
594
        Num1 when Num1 < Num ->
 
595
            ?number(Num1+1);
 
596
        Num1 ->
 
597
            ?number(Num1)
 
598
    end.
 
599
 
 
600
 
 
601
round(C, [Arg]) ->
 
602
    case mk_number(C, Arg) of
 
603
        A when atom(A) ->
 
604
            A;
 
605
        N when integer(N) ->
 
606
            N;
 
607
        F when float(F) ->
 
608
            round(F)
 
609
    end.
 
610
 
 
611
 
 
612
select_on_attribute([E = #xmlElement{attributes = Attrs}|T], K, V, Acc) ->
 
613
    case lists:keysearch(K, #xmlAttribute.name, Attrs) of
 
614
        {value, #xmlAttribute{value = V}} ->
 
615
            select_on_attribute(T, K, V, [E|Acc]);
 
616
        _ ->
 
617
            select_on_attribute(T, K, V, Acc)
 
618
    end;
 
619
select_on_attribute([], _K, _V, Acc) ->
 
620
    Acc.
 
621
 
 
622
 
 
623
%%%%
 
624
 
 
625
mk_nodeset(_C0, #xmlContext{nodeset = NS}) ->
 
626
    NS;
 
627
mk_nodeset(_C0, #xmlObj{type = nodeset, value = NS}) ->
 
628
    NS;
 
629
mk_nodeset(C0, Expr) ->
 
630
    case expr(Expr, C0) of
 
631
        #xmlObj{type = nodeset, value = NS} ->
 
632
            NS;
 
633
        Other ->
 
634
            exit({expected_nodeset, Other})
 
635
    end.
 
636
 
 
637
 
 
638
default_nodeset(#xmlContext{context_node = N}) ->
 
639
    [N].
 
640
 
 
641
 
 
642
mk_object(_C0, Obj = #xmlObj{}) ->
 
643
    Obj;
 
644
mk_object(C0, Expr) ->
 
645
    expr(Expr, C0).
 
646
 
 
647
 
 
648
mk_string(_C0, #xmlObj{type = string, value = V}) ->
 
649
    V;
 
650
mk_string(C0, Expr) ->
 
651
    mk_string(C0, expr(Expr, C0)).
 
652
 
 
653
 
 
654
 
 
655
mk_integer(_C0, #xmlObj{type = number, value = V}) when float(V)  ->
 
656
    round(V);
 
657
mk_integer(_C0, #xmlObj{type = number, value = V}) when integer(V)  ->
 
658
    V;
 
659
mk_integer(C, Expr) ->
 
660
    mk_integer(C, expr(Expr, C)).
 
661
 
 
662
 
 
663
mk_number(_C, #xmlObj{type = string, value = V}) ->
 
664
    scan_number(V);
 
665
mk_number(_C, #xmlObj{type = number, value = V}) ->
 
666
    V;
 
667
mk_number(C, N=#xmlObj{type = nodeset}) ->
 
668
    mk_number(C,string_value(N));
 
669
mk_number(_C, #xmlObj{type = boolean, value = false}) ->
 
670
    0;
 
671
mk_number(_C, #xmlObj{type = boolean, value = true}) ->
 
672
    1;
 
673
mk_number(C, Expr) ->
 
674
    mk_number(C, expr(Expr, C)).
 
675
 
 
676
 
 
677
mk_boolean(_C, #xmlObj{type = boolean, value = V}) -> 
 
678
    V;
 
679
mk_boolean(_C, #xmlObj{type = number, value = 0}) ->
 
680
    false;
 
681
mk_boolean(_C, #xmlObj{type = number, value = V}) when float(V) ; integer(V) ->
 
682
    true;
 
683
mk_boolean(_C, #xmlObj{type = nodeset, value = []}) ->
 
684
    false;
 
685
mk_boolean(_C, #xmlObj{type = nodeset, value = _V}) ->
 
686
    true;
 
687
mk_boolean(_C, #xmlObj{type = string, value = []}) ->
 
688
    false;
 
689
mk_boolean(_C, #xmlObj{type = string, value = _V}) ->
 
690
    true;
 
691
mk_boolean(C, Expr) ->
 
692
    mk_boolean(C, expr(Expr, C)).
 
693
 
 
694
 
 
695
normalize([H|T]) when ?whitespace(H) ->
 
696
    normalize(T);
 
697
normalize(Str) ->
 
698
    ContF = fun(_ContF, RetF, _S) ->
 
699
                    RetF()
 
700
            end,
 
701
    normalize(Str,
 
702
              #xmerl_scanner{acc_fun = fun() -> exit(acc_fun) end,
 
703
                             event_fun = fun() -> exit(event_fun) end,
 
704
                             hook_fun = fun() -> exit(hook_fun) end,
 
705
                             continuation_fun = ContF},
 
706
              []).
 
707
 
 
708
 
 
709
normalize(Str = [H|_], S, Acc) when ?whitespace(H) ->
 
710
    case xmerl_scan:accumulate_whitespace(Str, S, preserve, Acc) of
 
711
        {" " ++ Acc1, [], _S1} ->
 
712
            lists:reverse(Acc1);
 
713
        {Acc1, [], _S1} ->
 
714
            lists:reverse(Acc1);
 
715
        {Acc1, T1, S1} ->
 
716
            normalize(T1, S1, Acc1)
 
717
    end;
 
718
normalize([H|T], S, Acc) ->
 
719
    normalize(T, S, [H|Acc]);
 
720
normalize([], _S, Acc) ->
 
721
    lists:reverse(Acc).
 
722
 
 
723
 
 
724
scan_number([H|T]) when ?whitespace(H) ->
 
725
    scan_number(T);
 
726
scan_number("-" ++ T) ->
 
727
    case catch xmerl_xpath_scan:scan_number(T) of
 
728
        {{number, N}, Tail} ->
 
729
            case is_all_white(Tail) of
 
730
                true ->
 
731
                    N;
 
732
                false ->
 
733
                    'NaN'
 
734
            end;
 
735
        _Other ->
 
736
            'NaN'
 
737
    end;
 
738
scan_number(T) ->
 
739
    case catch xmerl_xpath_scan:scan_number(T) of
 
740
        {{number, N}, Tail} ->
 
741
            case is_all_white(Tail) of
 
742
                true ->
 
743
                    N;
 
744
                false ->
 
745
                    'NaN'
 
746
            end;
 
747
        _Other ->
 
748
            'NaN'
 
749
    end.
 
750
 
 
751
is_all_white([H|T]) when ?whitespace(H) ->
 
752
    is_all_white(T);
 
753
is_all_white([_H|_T]) ->
 
754
    false;
 
755
is_all_white([]) ->
 
756
    true.