~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
721
721
    %% Here we consider the DTD provided by doctype_DTD option,
722
722
    S1 =
723
723
        case S0 of
724
 
            #xmerl_scanner{validation=dtd,doctype_DTD=DTD} when list(DTD) ->
 
724
            #xmerl_scanner{validation=dtd,doctype_DTD=DTD} when is_list(DTD) ->
725
725
                S=fetch_DTD(undefined,S0),
726
726
                check_decl(S),
727
727
                S;
1185
1185
            S3 = fetch_DTD(Name, S2),
1186
1186
            check_decl(S3),
1187
1187
            scan_doctype3(T2, S3, DTD);
1188
 
        ExpRef when list(ExpRef) -> % Space added, see Section 4.4.8
 
1188
        ExpRef when is_list(ExpRef) -> % Space added, see Section 4.4.8
1189
1189
            {_,T3,S3} = strip(ExpRef++T2,S2),
1190
1190
            scan_doctype3(T3,S3,DTD)
1191
1191
    end;
1203
1203
 
1204
1204
 
1205
1205
 
1206
 
fetch_DTD(undefined, S=#xmerl_scanner{doctype_DTD=URI}) when list(URI)->
 
1206
fetch_DTD(undefined, S=#xmerl_scanner{doctype_DTD=URI}) when is_list(URI)->
1207
1207
    %% allow to specify DTD name when it isn't available in xml stream
1208
1208
    fetch_DTD({system,URI},S#xmerl_scanner{doctype_DTD=option_provided});
1209
1209
fetch_DTD(undefined, S) ->
1213
1213
fetch_DTD(DTDSpec, S)-> 
1214
1214
    case fetch_and_parse(DTDSpec,S,[{text_decl,true},
1215
1215
                                    {environment,{external,subset}}]) of
1216
 
        NewS when record(NewS,xmerl_scanner) ->
 
1216
        NewS when is_record(NewS,xmerl_scanner) ->
1217
1217
            NewS;
1218
1218
        {_Res,_Tail,_Sx} -> % Continue with old scanner data, result in Rules
1219
1219
            S
1326
1326
    case ets:match(Tab,{{notation,'$1'},undeclared}) of
1327
1327
        [[]] -> ok;
1328
1328
        [] ->  ok;
1329
 
        [L] when list(L) ->
 
1329
        [L] when is_list(L) ->
1330
1330
            ?fatal({error_missing_declaration_in_DTD,hd(L)},S);
1331
1331
        Err ->
1332
1332
            ?fatal({error_missing_declaration_in_DTD,Err},S)
1383
1383
    case ets:match(Tab,{{entity,'$1'},undeclared}) of
1384
1384
        [[]] -> ok;
1385
1385
        [] ->  ok;
1386
 
        [L] when list(L) ->
 
1386
        [L] when is_list(L) ->
1387
1387
            ?fatal({error_missing_declaration_in_DTD,hd(L)},S);
1388
1388
        Err ->
1389
1389
            ?fatal({error_missing_declaration_in_DTD,Err},S)
1401
1401
    case ets:match(Tab,{{id,'$1'},undeclared}) of
1402
1402
        [[]] -> ok;
1403
1403
        [] ->  ok;
1404
 
        [L] when list(L) ->
 
1404
        [L] when is_list(L) ->
1405
1405
            ?fatal({error_missing_declaration_in_DTD,hd(L)},S);
1406
1406
        Err ->
1407
1407
            ?fatal({error_missing_declaration_in_DTD,Err},S)
1439
1439
    {PERefName, T1, S1} = scan_pe_reference(T, S),
1440
1440
    {ExpandedRef,S2} =
1441
1441
        case expand_pe_reference(PERefName,S1,as_PE) of
1442
 
            Tuple when tuple(Tuple) ->
 
1442
            Tuple when is_tuple(Tuple) ->
1443
1443
                %% {system,URI} or {public,URI}
1444
1444
                {ExpRef,_Sx}=fetch_not_parse(Tuple,S1),
1445
1445
                {ExpRef,S1};
2231
2231
    {Name,T1,S1} = scan_pe_reference(T,S),
2232
2232
    {ExpandedRef,S2} = 
2233
2233
        case expand_pe_reference(Name,S1,in_literal) of
2234
 
            Tuple when tuple(Tuple) ->
 
2234
            Tuple when is_tuple(Tuple) ->
2235
2235
                %% {system,URI} or {public,URI}
2236
2236
                %% Included in literal, just get external file.
2237
2237
                {ExpRef,Sx}=fetch_not_parse(Tuple,S1),
2342
2342
            ok
2343
2343
    end,
2344
2344
    SName = if
2345
 
                list(Name) -> list_to_atom(Name);
 
2345
                is_list(Name) -> list_to_atom(Name);
2346
2346
                true -> Name
2347
2347
            end,
2348
2348
    case Read(id,SName,S) of
2678
2678
            ?fatal({unknown_parameter_entity, Name}, S); % WFC or VC failure
2679
2679
        Err={error,_Reason} ->
2680
2680
            ?fatal(Err,S);
2681
 
        Tuple when tuple(Tuple) ->
 
2681
        Tuple when is_tuple(Tuple) ->
2682
2682
            Tuple;
2683
2683
        Result ->
2684
2684
            if
3175
3175
    ?fatal({error,{validity_constraint_error_ID_Attribute_Default,Def}},S).
3176
3176
 
3177
3177
vc_Enumeration({_Name,{_,NameList},DefaultVal,_,_},S) 
3178
 
  when list(DefaultVal) ->    
 
3178
  when is_list(DefaultVal) ->    
3179
3179
    case lists:member(list_to_atom(DefaultVal),NameList) of
3180
3180
        true ->
3181
3181
            ok;
3185
3185
vc_Enumeration({_Name,{_,_NameList},_DefaultVal,_,_},_S) ->
3186
3186
    ok.
3187
3187
 
3188
 
vc_Entity_Name({_Name,'ENTITY',DefaultVal,_,_},S) when list(DefaultVal) ->
 
3188
vc_Entity_Name({_Name,'ENTITY',DefaultVal,_,_},S) when is_list(DefaultVal) ->
3189
3189
    Read = S#xmerl_scanner.rules_read_fun,
3190
3190
    case Read(entity,list_to_atom(DefaultVal),S) of
3191
3191
        {_,external,{_,{ndata,_}}} ->
3194
3194
    end;
3195
3195
vc_Entity_Name({_Name,'ENTITY',_,_,_},_S) ->
3196
3196
    ok;
3197
 
vc_Entity_Name({_,'ENTITIES',DefaultVal,_,_},S) when list(DefaultVal) ->
 
3197
vc_Entity_Name({_,'ENTITIES',DefaultVal,_,_},S) when is_list(DefaultVal) ->
3198
3198
    Read = S#xmerl_scanner.rules_read_fun,
3199
3199
    NameListFun = fun([],Acc,_St,_Fun) ->
3200
3200
                       lists:reverse(Acc);
3447
3447
                case expand_pe_reference(PERefName, S1, in_literal) of
3448
3448
                    %% actually should pe ref be expanded as_PE but
3449
3449
                    %% handle whitespace explicitly in this case.
3450
 
                    Tuple when tuple(Tuple) ->
 
3450
                    Tuple when is_tuple(Tuple) ->
3451
3451
                        %% {system,URI} or {public,URI}
3452
3452
                        %% Included in literal.
3453
3453
                        {ExpRef,Sx}=fetch_not_parse(Tuple,S1),