~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2003-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
399
399
 
400
400
%% +type valid_contents([rule()],[xmlElement()])->
401
401
%%              [xmlElement() | {error,???}.
402
 
valid_contents(Rule,XMLS,Rules,S,WSActionMode)->
403
 
    case parse(Rule,XMLS,Rules,WSActionMode,S) of
404
 
        {XML_N,[]}->
405
 
            lists:flatten(XML_N);
406
 
        {_,[#xmlElement{name=Name}|_T]} ->
407
 
            exit({error,{element,Name,isnt_comprise_in_the_rule,Rule}});
408
 
        {_,[#xmlText{}=Txt|_T]} ->
409
 
            exit({error,{element,text,Txt,isnt_comprise_in_the_rule,Rule}});
410
 
        {error,Reason} ->
411
 
            {error,Reason};
412
 
        {error,Reason,N} ->
413
 
            {error,Reason,N}
 
402
valid_contents(Rule, XMLS, Rules, S, WSActionMode)->
 
403
    case parse(Rule, XMLS, Rules, WSActionMode, S) of
 
404
        {error, Reason} ->
 
405
            {error, Reason};
 
406
        {error, Reason, N} ->
 
407
            {error, Reason, N};
 
408
        {XML_N, Rest} ->   %The list may consist of xmlComment{} records
 
409
            case lists:dropwhile(fun(X) when is_record(X, xmlComment) -> true; (_) -> false end, Rest) of 
 
410
                [] ->
 
411
                    lists:flatten(XML_N);
 
412
                [#xmlElement{name=Name} |_T] ->
 
413
                    exit({error, {element, Name, isnt_comprise_in_the_rule, Rule}});
 
414
                [#xmlText{} = Txt |_T] ->
 
415
                    exit({error, {element, text, Txt, isnt_comprise_in_the_rule, Rule}})
 
416
            end
414
417
    end.
415
418
 
416
 
parse({'*',SubRule},XMLS,Rules,WSaction,S)->
417
 
    star(SubRule,XMLS,Rules,WSaction,[],S); 
418
 
parse({'+',SubRule},XMLS,Rules,WSaction,S) ->
419
 
    plus(SubRule,XMLS,Rules,WSaction,S);
420
 
parse({choice,CHOICE},XMLS,Rules,WSaction,S)->
 
419
parse({'*', SubRule}, XMLS, Rules, WSaction, S)->
 
420
    star(SubRule, XMLS, Rules, WSaction, [], S); 
 
421
parse({'+',SubRule}, XMLS, Rules, WSaction, S) ->
 
422
    plus(SubRule, XMLS, Rules, WSaction, S);
 
423
parse({choice,CHOICE}, XMLS, Rules, WSaction, S)->
421
424
%    case XMLS of
422
425
%       [] ->
423
426
%           io:format("~p~n",[{choice,CHOICE,[]}]);
426
429
%       [#xmlText{value=V}|_] ->
427
430
%           io:format("~p~n",[{choice,CHOICE,{text,V}}])
428
431
%    end,
429
 
    choice(CHOICE,XMLS,Rules,WSaction,S);
430
 
parse(empty,[],_Rules,_WSaction,_S) ->
431
 
    {[],[]};
432
 
parse({'?',SubRule},XMLS,Rules,_WSaction,S)->
433
 
    question(SubRule,XMLS,Rules,S);
434
 
parse({seq,List},XMLS,Rules,WSaction,S) ->
435
 
    seq(List,XMLS,Rules,WSaction,S);
436
 
parse(El_Name,[#xmlElement{name=El_Name}=XML|T],Rules,_WSaction,S) 
 
432
    choice(CHOICE, XMLS, Rules, WSaction, S);
 
433
parse(empty, [], _Rules, _WSaction, _S) ->
 
434
    {[], []};
 
435
parse({'?', SubRule}, XMLS, Rules, _WSaction, S)->
 
436
    question(SubRule, XMLS, Rules, S);
 
437
parse({seq,List}, XMLS, Rules, WSaction, S) ->
 
438
    seq(List, XMLS, Rules, WSaction, S);
 
439
parse(El_Name, [#xmlElement{name=El_Name} = XML |T], Rules, _WSaction, S) 
437
440
  when is_atom(El_Name)->
438
 
    case do_validation(read_rules(Rules,El_Name),XML,Rules,S) of
439
 
        {error,R} ->
 
441
    case do_validation(read_rules(Rules, El_Name), XML, Rules, S) of
 
442
        {error, R} ->
440
443
%           {error,R};
441
444
            exit(R);
442
 
        {error,R,_N}->
 
445
        {error, R, _N}->
443
446
%           {error,R,N};
444
447
            exit(R);
445
448
        XML_->
446
 
            {[XML_],T}
447
 
    end;
448
 
parse(any,Cont,Rules,_WSaction,S) ->
449
 
    case catch parse_any(Cont,Rules,S) of
450
 
        Err = {error,_} -> Err;
451
 
        ValidContents -> {ValidContents,[]}
452
 
    end;
453
 
parse(El_Name,[#xmlElement{name=Name}|_T]=S,_Rules,_WSa,_S) when is_atom(El_Name)->
 
449
            {[XML_], T}
 
450
    end;
 
451
parse(any, Cont, Rules, _WSaction, S) ->
 
452
    case catch parse_any(Cont, Rules, S) of
 
453
        Err = {error, _} -> Err;
 
454
        ValidContents -> {ValidContents, []}
 
455
    end;
 
456
parse(El_Name, [#xmlElement{name=Name} |_T] = XMLS, _Rules, _WSa, _S) when is_atom(El_Name) ->
454
457
    {error,
455
 
     {element_seq_not_conform,{wait,El_Name},{is,Name}},
456
 
     {{next,S},{act,[]}} };
457
 
parse(_El_Name,[#xmlPI{}=H|T],_Rules,_WSa,_S) ->
458
 
    {[H],T};
459
 
parse('#PCDATA',XML,_Rules,_WSa,_S)->
 
458
     {element_seq_not_conform,{wait, El_Name}, {is, Name}},
 
459
     {{next, XMLS}, {act, []}}};
 
460
parse(El_Name, [#xmlComment{} |T], Rules, WSa, S) ->
 
461
    parse(El_Name, T, Rules, WSa, S);
 
462
parse(_El_Name, [#xmlPI{} = H |T], _Rules, _WSa, _S) ->
 
463
    {[H], T};
 
464
parse('#PCDATA', XMLS, _Rules, _WSa, _S)->
460
465
    %%% PCDATA it is 0 , 1 or more #xmlText{}.
461
 
    parse_pcdata(XML);
462
 
parse(El_Name,[#xmlText{}|_T]=S,_Rules,_WSa,_S)->
 
466
    parse_pcdata(XMLS);
 
467
parse(El_Name, [#xmlText{}|_T] = XMLS, _Rules, _WSa, _S)->
463
468
    {error,
464
 
     {text_in_place_of,El_Name},
465
 
     {{next,S},{act,[]}}};
466
 
parse([],_,_,_,_) ->
467
 
    {error,no_rule};
468
 
parse(Rule,[],_,_,_) ->
469
 
    {error,{no_xml_element,Rule}}.
 
469
     {text_in_place_of, El_Name},
 
470
     {{next, XMLS}, {act, []}}};
 
471
parse([], _, _, _, _) ->
 
472
    {error, no_rule};
 
473
parse(Rule, [], _, _, _) ->
 
474
    {error, {no_xml_element, Rule}}.
470
475
 
471
476
parse_any([],_Rules,_S) ->
472
477
    [];
618
623
 
619
624
parse_pcdata([#xmlText{}=H|T])->
620
625
    parse_pcdata(T,[H]);
 
626
parse_pcdata([#xmlComment{}|T])->
 
627
    parse_pcdata(T,[]);
621
628
parse_pcdata(H) ->
622
629
    {[],H}.
623
630
 
624
631
parse_pcdata([#xmlText{}=H|T],Acc)->
625
632
    parse_pcdata(T,Acc++[H]);
 
633
parse_pcdata([#xmlComment{}|T],Acc)->
 
634
    parse_pcdata(T,Acc);
626
635
parse_pcdata(H,Acc) ->
627
636
    {Acc,H}.
628
637