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

« back to all changes in this revision

Viewing changes to lib/xmerl/src/xmerl_xpath.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:
101
101
 
102
102
-record(state, {context = #xmlContext{},
103
103
                acc = []}).
104
 
%% -record(node, {node,
105
 
%%             pos,
106
 
%%             parents}).
 
104
 
107
105
 
108
106
-define(nodeset(NS), #state{context = #xmlContext{nodeset = NS}}).
109
107
-define(context(C), #state{context = C}).
111
109
 
112
110
 
113
111
 
114
 
%% @spec string(Str, Doc) -> docEntity()
 
112
%% @spec string(Str, Doc) -> [docEntity()] | Scalar
115
113
%% @equiv string(Str,Doc, [])
116
114
string(Str, Doc) ->
117
115
    string(Str, Doc, []).
118
116
 
119
117
%% @spec string(Str,Doc,Options) -> 
120
 
%%      docEntity()
 
118
%%      [docEntity()] | Scalar
121
119
%% @equiv string(Str,Doc, [],Doc,Options)
122
120
string(Str, Doc, Options) ->
123
121
    string(Str, Doc, [], Doc, Options).
124
122
 
125
123
%% @spec string(Str,Node,Parents,Doc,Options) ->
126
 
%%      docEntity()
 
124
%%      [docEntity()] | Scalar
127
125
%%   Str     = xPathString()
128
126
%%   Node    = nodeEntity()
129
127
%%   Parents = parentList()
130
128
%%   Doc     = nodeEntity()
131
129
%%   Options = option_list()
 
130
%%   Scalar  = xmlObj
132
131
%% @doc Extracts the nodes from the parsed XML tree according to XPath.
 
132
%%   xmlObj is a record with fields type and value,
 
133
%%   where type is boolean | number | string
133
134
string(Str, Node, Parents, Doc, Options) ->
 
135
%% record with fields type and value,
 
136
%%                where type is boolean | number | string
134
137
    FullParents = 
135
138
        case Parents of
136
139
            [] ->
148
151
    Context=(new_context(Options))#xmlContext{context_node = ContextNode,
149
152
                                              whole_document = WholeDoc},
150
153
%io:format("string Context=~p~n",[Context]),
151
 
    #state{context =  NewContext} = match(Str, #state{context = Context}),
 
154
    #state{context = NewContext} = match(Str, #state{context = Context}),
152
155
%io:format("string NewContext=~p~n",[NewContext]),
153
 
    [N || #xmlNode{node = N} <- NewContext#xmlContext.nodeset].
 
156
    case NewContext#xmlContext.nodeset of
 
157
        ScalObj = #xmlObj{type=Scalar} 
 
158
        when Scalar == boolean; Scalar == number; Scalar == string ->
 
159
            ScalObj;
 
160
        #xmlObj{type=nodeset,value=NodeSet} -> 
 
161
            NodeSet;
 
162
        _ ->
 
163
            [N || #xmlNode{node = N} <- NewContext#xmlContext.nodeset]
 
164
    end.
154
165
 
155
166
 
156
167
whole_document(#xmlDocument{} = Doc) ->
218
229
 
219
230
 
220
231
match_expr({path, Type, Arg}, S) ->
221
 
    eval_path(Type, Arg, S#state.context).
 
232
    eval_path(Type, Arg, S#state.context);
 
233
%% PrimaryExpr
 
234
match_expr(PrimExpr,S) ->
 
235
    eval_primary_expr(PrimExpr,S).
222
236
 
223
237
 
224
238
 
236
250
                                                         acc = Acc}) ->
237
251
    ?dbg("PredExpr = ~p~n", [PredExpr]),
238
252
    NewContext = axis(Axis, NodeTest, C, Acc),
239
 
    pred_expr(PredExpr, S#state{context = NewContext}).
240
 
 
 
253
    pred_expr(PredExpr, S#state{context = NewContext});
 
254
path_expr('/', S) ->
 
255
    S.
241
256
 
242
257
 
243
258
pred_expr([], S) ->
250
265
%% simple case: the predicate is a number, e.g. para[5].
251
266
%% No need to iterate over all nodes in the nodeset; we know what to do.
252
267
%%
253
 
eval_pred({number, N}, S = #state{context = C = #xmlContext{nodeset = NS}}) ->
254
 
    case length(NS)>=N of
 
268
eval_pred({number, N0}, 
 
269
          S = #state{context = C = #xmlContext{nodeset = NS,
 
270
                                               axis_type = AxisType}}) ->
 
271
    Len = length(NS),
 
272
    case Len>=N0 of
255
273
        true ->
 
274
            N = case AxisType of
 
275
                    forward ->
 
276
                        N0;
 
277
                    reverse ->
 
278
                        Len + 1 - N0
 
279
                end,
256
280
            NewNodeSet = [lists:nth(N, NS)],
257
281
            NewContext = C#xmlContext{nodeset = NewNodeSet},
258
282
            S#state{context = NewContext};
297
321
eval_path(union, {PathExpr1, PathExpr2}, C = #xmlContext{}) ->
298
322
    S = #state{context = C},
299
323
    S1 = match_expr(PathExpr1, S),
300
 
    NewNodeSet = (S#state.context)#xmlContext.nodeset,
301
 
    match_expr(PathExpr2, S1#state{acc = NewNodeSet});
 
324
%%    NewNodeSet = (S1#state.context)#xmlContext.nodeset,
 
325
    S2 = match_expr(PathExpr2, S1#state{context=C}),
 
326
    NodeSet1 = (S1#state.context)#xmlContext.nodeset,
 
327
    NodeSet2 = (S2#state.context)#xmlContext.nodeset,
 
328
    NewNodeSet = ordsets:to_list(ordsets:union(ordsets:from_list(NodeSet1),
 
329
                                               ordsets:from_list(NodeSet2))),
 
330
    S2#state{context=(S2#state.context)#xmlContext{nodeset=NewNodeSet}};
302
331
eval_path(abs, PathExpr, C = #xmlContext{}) ->
303
332
    NodeSet = [C#xmlContext.whole_document],
304
333
    Context = C#xmlContext{nodeset = NodeSet},
314
343
    S1 = path_expr(PathExpr, S),
315
344
    pred_expr(PredExpr, S1).
316
345
 
 
346
eval_primary_expr(FC = {function_call,_,_},S = #state{context = Context}) ->
 
347
%%    NewNodeSet = xmerl_xpath_pred:eval(FC, Context),
 
348
    NewNodeSet = xmerl_xpath_lib:eval(primary_expr, FC, Context),
 
349
    NewContext = Context#xmlContext{nodeset = NewNodeSet},
 
350
    S#state{context = NewContext};
 
351
eval_primary_expr(PrimExpr,_S) ->
 
352
    exit({primary_expression,{not_implemented, PrimExpr}}).
 
353
    
317
354
 
318
355
%% axis(Axis,NodeTest,Context::xmlContext()) -> xmlContext()
319
356
%% axis(Axis,NodeTest,Context,[])
365
402
 
366
403
fwd_or_reverse(ancestor, Context) ->
367
404
    reverse_axis(Context);
 
405
fwd_or_reverse(ancestor_or_self, Context) ->
 
406
    reverse_axis(Context);
368
407
fwd_or_reverse(preceding_sibling, Context) ->
369
408
    reverse_axis(Context);
370
409
fwd_or_reverse(preceding, Context) ->
382
421
match_self(Tok, N, Acc, Context) ->
383
422
    case node_test(Tok, N, Context) of
384
423
        true ->
385
 
            %io:format("node_test -> true.~n", []),
386
424
            [N|Acc];
387
425
        false ->
388
426
            Acc
393
431
    #xmlNode{parents = Ps, node = Node, type = Type} = N,
394
432
    case Type of
395
433
        El when El == element; El == root_node ->
396
 
%       element ->
397
434
            NewPs = [N|Ps],
398
435
            match_desc(get_content(Node), NewPs, Tok, Acc, Context);
399
436
        _Other ->
400
437
            Acc
401
438
    end.
402
439
 
403
 
%match_desc(Content, Parents, Tok, Context) ->
404
 
%    match_desc(Content, Parents, Tok, [], Context).
405
440
 
406
441
match_desc([E = #xmlElement{}|T], Parents, Tok, Acc, Context) ->
 
442
    Acc1 = match_desc(T, Parents, Tok, Acc, Context),
407
443
    N = #xmlNode{type = node_type(E),
408
444
                 node = E,
409
445
                 parents = Parents},
410
446
    NewParents = [N|Parents],
411
 
    Acc1 = case node_test(Tok, N, Context) of
412
 
               true ->
413
 
                   [N|Acc];
414
 
               false ->
415
 
                   Acc
416
 
           end,
417
447
    Acc2 = match_desc(get_content(E), NewParents, Tok, Acc1, Context),
418
 
    match_desc(T, Parents, Tok, Acc2, Context);
 
448
    match_self(Tok, N, Acc2, Context);
419
449
match_desc([E|T], Parents, Tok, Acc, Context) ->
 
450
    Acc1 = match_desc(T, Parents, Tok, Acc, Context),
420
451
    N = #xmlNode{node = E,
421
452
                 type = node_type(E),
422
453
                 parents = Parents},
423
 
    Acc1 = case node_test(Tok, N, Context) of
424
 
               true ->
425
 
                   [N|Acc];
426
 
               false ->
427
 
                   Acc
428
 
           end,
429
 
    match_desc(T, Parents, Tok, Acc1, Context);
 
454
    match_self(Tok, N, Acc1, Context);
430
455
match_desc([], _Parents, _Tok, Acc, _Context) ->
431
456
    Acc.
432
457
                          
435
460
%% "The 'descendant-or-self' axis contains the context node and the 
436
461
%% descendants of the context node."
437
462
match_descendant_or_self(Tok, N, Acc, Context) ->
438
 
    Acc1 = case node_test(Tok, N, Context) of
439
 
               true ->
440
 
                   [N|Acc];
441
 
               false ->
442
 
                   Acc
443
 
           end,
444
 
    match_descendant(Tok, N, Acc1, Context).
 
463
    Acc1 = match_descendant(Tok, N, Acc, Context),
 
464
    match_self(Tok, N, Acc1, Context).
445
465
 
446
466
 
447
467
match_child(Tok, N, Acc, Context) ->
455
475
                      ThisN = #xmlNode{type = node_type(E),
456
476
                                       node = E,
457
477
                                       parents = NewPs},
458
 
                      case node_test(Tok, ThisN, Context) of
459
 
                          true ->
460
 
                              [ThisN|AccX];
461
 
                          false ->
462
 
                              AccX
463
 
                      end
 
478
                      match_self(Tok, ThisN, AccX, Context)
464
479
              end, Acc, get_content(Node));
465
480
        _Other ->
466
481
            Acc
474
489
        [] ->
475
490
            Acc;
476
491
        [PN|_] ->
477
 
            case node_test(Tok, PN, Context) of
478
 
                true ->
479
 
                    [PN|Acc];
480
 
                false ->
481
 
                    Acc
482
 
            end
 
492
            match_self(Tok, PN, Acc, Context)
483
493
    end.
484
494
 
485
495
 
489
499
%% always include the root node, unless the context node is the root node."
490
500
match_ancestor(Tok, N, Acc, Context) ->
491
501
    Parents = N#xmlNode.parents,
492
 
    lists:foldr(
 
502
    lists:foldl(
493
503
      fun(PN, AccX) ->
494
 
              case node_test(Tok, PN, Context) of
495
 
                  true ->
496
 
                      [PN|AccX];
497
 
                  false ->
498
 
                      AccX
499
 
              end
 
504
              match_self(Tok, PN, AccX, Context)
500
505
      end, Acc, Parents).
501
506
 
502
507
 
506
511
%% of the context node; thus, the acestor axis will always include the
507
512
%% root node."
508
513
match_ancestor_or_self(Tok, N, Acc, Context) ->
509
 
    Acc1 = case node_test(Tok, N, Context) of
510
 
               true ->
511
 
                   [N|Acc];
512
 
               false ->
513
 
                   Acc
514
 
           end,
 
514
    Acc1 = match_self(Tok, N, Acc, Context),
515
515
    match_ancestor(Tok, N, Acc1, Context).
516
516
 
517
517
 
525
525
    case Ps of
526
526
        [#xmlNode{type = element,
527
527
                  node = #xmlElement{} = PNode}|_] ->
528
 
            FollowingSiblings = lists:nthtail(Node#xmlElement.pos, 
 
528
            FollowingSiblings = lists:nthtail(get_position(Node), 
529
529
                                              get_content(PNode)),
530
530
            lists:foldr(
531
531
              fun(E, AccX) ->
532
532
                      ThisN = #xmlNode{type = node_type(E),
533
533
                                       node = E,
534
534
                                       parents = Ps},
535
 
                      case node_test(Tok, ThisN, Context) of
536
 
                          true ->
537
 
                              [ThisN|AccX];
538
 
                          false ->
539
 
                              AccX
540
 
                      end
 
535
                      match_self(Tok, ThisN, AccX, Context)
541
536
              end, Acc, FollowingSiblings);
542
537
        _Other ->
543
538
            Acc
547
542
%% "The 'following' axis contains all nodes in the same document as the
548
543
%% context node that are after the context node in document order, excluding
549
544
%% any descendants and excluding attribute nodes and namespace nodes."
550
 
%% (UW: I interpret this as "following siblings and their descendants")
551
545
match_following(Tok, N, Acc, Context) ->
552
546
    #xmlNode{parents = Ps, node = Node} = N,
553
547
    case Ps of
554
548
        [#xmlNode{type = element,
555
 
                  node = #xmlElement{} = PNode}|_] ->
556
 
            FollowingSiblings = lists:nthtail(Node#xmlElement.pos, 
 
549
                  node = #xmlElement{} = PNode} = P|_] ->
 
550
            FollowingSiblings = lists:nthtail(get_position(Node), 
557
551
                                              get_content(PNode)),
 
552
            Acc0 = match_following(Tok, P, Acc, Context),
558
553
            lists:foldr(
559
554
              fun(E, AccX) ->
560
555
                      ThisN = #xmlNode{type = node_type(E),
561
556
                                       node = E,
562
557
                                       parents = Ps},
563
 
                      Acc1 =
564
 
                          case node_test(Tok, ThisN, Context) of
565
 
                              true ->
566
 
                                  [ThisN|AccX];
567
 
                              false ->
568
 
                                  AccX
569
 
                          end,
570
 
                      match_desc(get_content(E), Tok, Ps, Acc1, Context)
571
 
              end, Acc, FollowingSiblings);
 
558
                      match_descendant_or_self(Tok, ThisN, AccX, Context)
 
559
              end, Acc0, FollowingSiblings);
572
560
        _Other ->
573
561
            Acc
574
562
    end.
588
576
        [#xmlNode{type = element,
589
577
                  node = #xmlElement{} = PNode}|_] ->
590
578
            PrecedingSiblings = lists:sublist(get_content(PNode), 1,
591
 
                                              Node#xmlElement.pos-1), 
 
579
                                              get_position(Node) - 1), 
592
580
            lists:foldr(
593
581
              fun(E, AccX) ->
594
582
                      ThisN = #xmlNode{type = node_type(E),
595
583
                                       node = E,
596
584
                                       parents = Ps},
597
 
                      case node_test(Tok, ThisN, Context) of
598
 
                          true ->
599
 
                              [ThisN|AccX];
600
 
                          false ->
601
 
                              AccX
602
 
                      end
 
585
                      match_self(Tok, ThisN, AccX, Context)
603
586
              end, Acc, PrecedingSiblings);
604
587
        _Other ->
605
 
            []
 
588
            Acc
606
589
    end.
607
590
 
608
591
 
609
592
%% "The 'preceding' axis contains all nodes in the same document as the context
610
593
%% node that are before the context node in document order, exluding any
611
594
%% ancestors and excluding attribute nodes and namespace nodes."
612
 
%% (UW: I interpret this as "preceding siblings and their descendants".)
613
595
match_preceding(Tok, N, Acc, Context) ->
614
596
    #xmlNode{parents = Ps, node = Node} = N,
615
597
    case Ps of
616
598
        [#xmlNode{type = element,
617
 
                  node = #xmlElement{} = PNode}|_] ->
 
599
                  node = #xmlElement{} = PNode} = P|_] ->
618
600
            PrecedingSiblings = lists:sublist(get_content(PNode), 1,
619
 
                                              Node#xmlElement.pos-1), 
620
 
            lists:foldr(
621
 
              fun(E, AccX) ->
622
 
                      ThisN = #xmlNode{type = node_type(E),
623
 
                                       node = E,
624
 
                                       parents = Ps},
625
 
                      Acc1 =
626
 
                          case node_test(Tok, ThisN, Context) of
627
 
                              true ->
628
 
                                  [ThisN|AccX];
629
 
                                  false ->
630
 
                                      AccX
631
 
                          end,
632
 
                      match_desc(get_content(E), Tok, Ps, Acc1, Context)
633
 
              end, Acc, PrecedingSiblings);
 
601
                                              get_position(Node) - 1), 
 
602
            Acc0 = lists:foldr(
 
603
                     fun(E, AccX) ->
 
604
                             ThisN = #xmlNode{type = node_type(E),
 
605
                                              node = E,
 
606
                                              parents = Ps},
 
607
                             match_descendant_or_self(Tok, ThisN,
 
608
                                                      AccX, Context)
 
609
                     end, Acc, PrecedingSiblings),
 
610
            match_preceding(Tok, P, Acc0, Context);
634
611
        _Other ->
635
 
            []
 
612
            Acc
636
613
    end.
637
614
 
638
615
 
642
619
    case N#xmlNode.type of
643
620
        element ->
644
621
            #xmlNode{parents = Ps, node = E} = N,
645
 
            lists:foldl(
 
622
            lists:foldr(
646
623
              fun(A, AccX) ->
647
624
                      ThisN = #xmlNode{type = attribute,
648
625
                                       node = A,
649
626
                                       parents = [N|Ps]},
650
 
                      case node_test(Tok, ThisN, Context) of
651
 
                          true ->
652
 
                              [ThisN|AccX];
653
 
                          false ->
654
 
                              AccX
655
 
                      end
 
627
                      match_self(Tok, ThisN, AccX, Context)
656
628
              end, Acc, E#xmlElement.attributes);
657
629
        _Other ->
658
 
            []
 
630
            %%[]
 
631
            Acc
659
632
    end.
660
633
 
661
634
node_type(#xmlAttribute{}) ->   attribute;
672
645
%    erlang:fault(not_yet_implemented).
673
646
 
674
647
 
675
 
update_nodeset(Context = #xmlContext{axis_type = reverse}, NodeSet) ->
676
 
    Context#xmlContext{nodeset = reverse(NodeSet)};
677
 
update_nodeset(Context, NodeSet) ->
678
 
    Context#xmlContext{nodeset = forward(NodeSet)}.
679
 
 
680
 
reverse(NodeSet) ->
681
 
    reverse(NodeSet, 1, []).
682
 
 
683
 
reverse([H|T], Pos, Acc) ->
684
 
    reverse(T, Pos+1, [H#xmlNode{pos = Pos}|Acc]);
685
 
reverse([], _Pos, Acc) ->
686
 
    Acc.
687
 
 
688
 
forward(NodeSet) ->
689
 
    forward(NodeSet, 1).
690
 
 
691
 
forward([H|T], Pos) ->
692
 
    [H#xmlNode{pos = Pos}|forward(T, Pos+1)];
693
 
forward([], _Pos) ->
694
 
    [].
 
648
update_nodeset(Context = #xmlContext{axis_type = AxisType}, NodeSet) ->
 
649
    MapFold =
 
650
        case AxisType of
 
651
            forward ->
 
652
                mapfoldl;
 
653
            reverse ->
 
654
                mapfoldr
 
655
        end,
 
656
    {Result, _N} =
 
657
        lists:MapFold(fun(Node, N) ->
 
658
                              {Node#xmlNode{pos = N}, N + 1}
 
659
                      end, 1, NodeSet),
 
660
    Context#xmlContext{nodeset = Result}.
695
661
 
696
662
 
697
663
 
736
702
    case expanded_name(Prefix, Local, Context) of
737
703
        [] ->
738
704
            ?dbg("node_test(~p, ~p) -> ~p.~n", 
739
 
                 [{Tag, Prefix, Local}, write_node(Name), false]),
 
705
                 [{_Tag, Prefix, Local}, write_node(Name), false]),
740
706
            false;
741
707
        ExpName ->
742
708
            Res = (ExpName == {NS#xmlNamespace.default,Name}),
743
709
            ?dbg("node_test(~p, ~p) -> ~p.~n", 
744
 
                 [{Tag, Prefix, Local}, write_node(Name), Res]),
 
710
                 [{_Tag, Prefix, Local}, write_node(Name), Res]),
745
711
            Res
746
712
    end;
747
713
node_test({name, {Tag,_Prefix,_Local}}, 
812
778
    C;
813
779
get_content(#xmlDocument{content = C}) ->
814
780
    [C].
 
781
 
 
782
 
 
783
get_position(#xmlElement{pos = N}) ->
 
784
    N;
 
785
get_position(#xmlText{pos = N}) ->
 
786
    N.