~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
52
52
         last/2,
53
53
         'local-name'/2,
54
54
         'namespace-uri'/2,
 
55
         name/2,
 
56
         string/2,
55
57
         nodeset/1,
56
58
         'normalize-space'/2,
57
59
         number/1, number/2,
65
67
         'substring-before'/2,
66
68
         sum/2,
67
69
         translate/2]).
68
 
         
 
70
-export([core_function/1]).      
69
71
 
70
72
-include("xmerl.hrl").
71
73
-include("xmerl_xpath.hrl").
181
183
comp_expr('!=', E1, E2, C) ->
182
184
    N1 = expr(E1,C),
183
185
    N2 = expr(E2,C),
184
 
    ?boolean(compare_eq_format(N1,N2,C) == compare_eq_format(N2,N1,C)).
 
186
    ?boolean(compare_eq_format(N1,N2,C) /= compare_eq_format(N2,N1,C)).
185
187
 
186
188
bool_expr('or', E1, E2, C) ->
187
189
    ?boolean(mk_boolean(C, E1) or mk_boolean(C, E2));
283
285
 
284
286
%% node-set: id(object)
285
287
id(C, [Arg]) ->
286
 
    NS0 = [C#xmlContext.whole_document],
287
 
    case Arg#xmlObj.type of
 
288
    WD = C#xmlContext.whole_document,
 
289
    NS0 = [WD],
 
290
    Obj = mk_object(C,Arg),
 
291
    case Obj#xmlObj.type of
288
292
        nodeset ->
289
 
            NodeSet = Arg#xmlObj.value,
 
293
            NodeSet = Obj#xmlObj.value,
290
294
            IdTokens = 
291
295
                lists:foldl(
292
296
                  fun(N, AccX) ->
301
305
                                 end, C#xmlContext{nodeset = NS0}),
302
306
            ?nodeset(NewNodeSet);
303
307
        _ ->
304
 
            StrVal = string_value(Arg#xmlObj.value),
 
308
            StrVal = string_value(Obj#xmlObj.value),
305
309
            IdTokens = id_tokens(StrVal),
306
 
            lists:foldl(
307
 
              fun(Tok, AccX) ->
308
 
                      select_on_attribute(NS0, id, Tok, AccX)
309
 
              end, [], IdTokens)
 
310
            NodeSet = [(WD#xmlNode.node)#xmlDocument.content],
 
311
            NewNodeSet = lists:foldl(
 
312
                           fun(Tok, AccX) ->
 
313
                                   select_on_attribute(NodeSet, id, Tok, AccX)
 
314
                           end, [], IdTokens),
 
315
            ?nodeset(NewNodeSet)
 
316
            
310
317
    end.
311
318
 
312
319
id_tokens(Str=#xmlObj{type=string}) ->
336
343
 
337
344
local_name1([]) ->
338
345
    ?string([]);
 
346
local_name1([#xmlNode{type=element,node=El}|_]) ->
 
347
    #xmlElement{name=Name,nsinfo=NSI} = El,
 
348
    local_name2(Name,NSI);
 
349
local_name1([#xmlNode{type=attribute,node=Att}|_]) ->
 
350
    #xmlAttribute{name=Name,nsinfo=NSI} = Att,
 
351
    local_name2(Name,NSI);
339
352
local_name1([#xmlElement{name = Name, nsinfo = NSI}|_]) ->
 
353
    local_name2(Name,NSI).
 
354
local_name2(Name, NSI) ->
340
355
    case NSI of
341
356
        {_Prefix, Local} ->
342
357
            ?string(Local);
343
358
        [] ->
344
 
            ?string(Name)
 
359
            ?string(atom_to_list(Name))
345
360
    end.
346
361
 
347
362
%% string: namespace-uri(node-set?)
355
370
ns_uri([]) ->
356
371
    ?string([]);
357
372
ns_uri([#xmlElement{nsinfo = NSI, namespace = NS}|_]) ->
 
373
    ns_uri2(NSI,NS);
 
374
ns_uri([#xmlNode{type=element,node=El}|_]) ->
 
375
    #xmlElement{nsinfo=NSI, namespace = NS} = El,
 
376
    ns_uri2(NSI,NS);
 
377
ns_uri([#xmlNode{type=attribute,node=Att}|_]) ->
 
378
    #xmlAttribute{nsinfo=NSI, namespace = NS} = Att,
 
379
    ns_uri2(NSI,NS);
 
380
ns_uri(_) ->
 
381
    ?string([]).
 
382
 
 
383
ns_uri2(NSI,NS) ->
358
384
    case NSI of
359
385
        {Prefix, _} ->
360
386
            case lists:keysearch(Prefix, 1, NS#xmlNamespace.nodes) of
361
387
                false ->
362
388
                    ?string([]);
363
389
                {value, {_K, V}} ->
364
 
                    ?string(V)
 
390
                    string_value(V)
365
391
            end;
366
392
        [] ->
367
 
            []
 
393
            ?string([])
368
394
    end.
369
395
 
370
 
 
 
396
%% name(node-set) -> xmlObj{type=string}
 
397
%% The name function returns a string containing the QName of the node
 
398
%% first in document order. The representation of the QName is not
 
399
%% standardized and applications have their own format. At
 
400
%% http://xml.coverpages.org/clarkNS-980804.html (the author of XPath)
 
401
%% adopts the format "namespace URI"+"local-name" but according to
 
402
%% other sources it is more common to use the format:
 
403
%% '{'"namespace URI"'}'"local-name". This function also uses this
 
404
%% latter form.
 
405
name(C,[]) ->
 
406
    name1(default_nodeset(C));
 
407
name(C, [Arg]) ->
 
408
    name1(mk_nodeset(C, Arg)).
 
409
name1([]) ->
 
410
    ?string([]);
 
411
name1(NodeSet) ->
 
412
    NSVal =
 
413
        case ns_uri(NodeSet) of
 
414
            #xmlObj{value=NSStr} when NSStr =/= [] ->
 
415
                "{"++NSStr++"}";
 
416
            _ ->
 
417
                ""
 
418
        end,
 
419
    #xmlObj{value=LocalName} = local_name1(NodeSet),
 
420
    ?string(NSVal++LocalName).
 
421
        
 
422
          
371
423
 
372
424
%%% String functions
373
425
 
399
451
                     end,
400
452
    TextDecendants=fun(X) -> TextValue(X,TextValue) end,
401
453
    ?string(lists:flatten(lists:map(TextDecendants,C)));
 
454
string_value(T=#xmlNode{type=text}) ->
 
455
    #xmlText{value=Txt} = T#xmlNode.node,
 
456
    ?string(Txt);
402
457
string_value(infinity) -> ?string("Infinity");
403
458
string_value(neg_infinity) -> ?string("-Infinity");
404
459
string_value(A) when atom(A) ->
407
462
    ?string(integer_to_list(N));
408
463
string_value(N) when float(N) ->
409
464
    N1 = round(N * 10000000000000000),
410
 
    ?string(strip_zeroes(integer_to_list(N1))).
 
465
    ?string(strip_zeroes(integer_to_list(N1)));
 
466
string_value(Str) when is_list(Str) ->
 
467
    ?string(Str).
411
468
 
412
469
strip_zeroes(Str) ->
413
470
    strip_zs(lists:reverse(Str), 15).
432
489
 
433
490
%% boolean: starts-with(string, string)
434
491
'starts-with'(C, [A1, A2]) ->
435
 
    ?boolean(lists:prefix(mk_string(C, A1), mk_string(C, A2))).
 
492
    ?boolean(lists:prefix(mk_string(C, A2), mk_string(C, A1))).
436
493
 
437
494
%% boolean: contains(string, string)
438
495
contains(C, [A1, A2]) ->
613
670
select_on_attribute([E = #xmlElement{attributes = Attrs}|T], K, V, Acc) ->
614
671
    case lists:keysearch(K, #xmlAttribute.name, Attrs) of
615
672
        {value, #xmlAttribute{value = V}} ->
616
 
            select_on_attribute(T, K, V, [E|Acc]);
 
673
            Acc2 = select_on_attribute(E#xmlElement.content,K,V,[E|Acc]),
 
674
            select_on_attribute(T, K, V, Acc2);
617
675
        _ ->
618
 
            select_on_attribute(T, K, V, Acc)
 
676
            Acc2 = select_on_attribute(E#xmlElement.content,K,V,Acc),
 
677
            select_on_attribute(T, K, V, Acc2)
619
678
    end;
 
679
select_on_attribute([H|T], K, V, Acc) when is_record(H,xmlText) ->
 
680
    select_on_attribute(T, K, V, Acc);
620
681
select_on_attribute([], _K, _V, Acc) ->
621
682
    Acc.
622
683
 
648
709
 
649
710
mk_string(_C0, #xmlObj{type = string, value = V}) ->
650
711
    V;
 
712
mk_string(C0, Obj = #xmlObj{}) ->
 
713
    mk_string(C0,string_value(Obj));
651
714
mk_string(C0, Expr) ->
652
715
    mk_string(C0, expr(Expr, C0)).
653
716