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

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1ct_parser2.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:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%<copyright>
 
2
%% <year>2000-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
 
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 2000, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
16
%%
 
17
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
17
19
%%
18
20
-module(asn1ct_parser2).
19
21
 
177
179
        end,
178
180
    {SymbolList,Rest} = parse_SymbolList(Tokens),
179
181
    case Rest of
180
 
        %%How does this case correspond to x.680 ?
181
182
        [{'FROM',_L1},Tref = {typereference,_,Name},Ref={identifier,_L2,_Id},C={',',_}|Rest2] ->
182
183
            NewSymbolList = lists:map(SetRefModuleName(Name),SymbolList),
183
184
            {#'SymbolsFromModule'{symbols=NewSymbolList,
184
185
                                  module=tref2Exttref(Tref)},[Ref,C|Rest2]};
185
 
        %%How does this case correspond to x.680 ?
 
186
 
 
187
        %% This a special case when there is only one Symbol imported
 
188
        %% from the next module. No other way to distinguish Ref from
 
189
        %% a part of the GlobalModuleReference of Name.
 
190
        [{'FROM',_L1},Tref = {typereference,_,Name},Ref = {identifier,_L2,_Id},From = {'FROM',_}|Rest2] ->
 
191
            NewSymbolList = lists:map(SetRefModuleName(Name),SymbolList),
 
192
            {#'SymbolsFromModule'{symbols=NewSymbolList,
 
193
                                  module=tref2Exttref(Tref)},[Ref,From|Rest2]};
186
194
        [{'FROM',_L1},Tref = {typereference,_,Name},{identifier,_L2,_Id}|Rest2] ->
187
195
            NewSymbolList = lists:map(SetRefModuleName(Name),SymbolList),
188
196
            {#'SymbolsFromModule'{symbols=NewSymbolList,
277
285
        [] ->
278
286
            throw({asn1_error,{parse_or,ErrList}});
279
287
        L when list(L) ->
280
 
%%%         throw({asn1_error,{parse_or,hd(lists:reverse(ErrList))}});
281
288
            %% chose to throw 1) the error with the highest line no,
282
289
            %% 2) the last error which is not a asn1_assignment_error or
283
290
            %% 3) the last error.
293
300
            parse_or(Tokens,Frest,[AsnAssErr|ErrList]);
294
301
        Result = {_,L} when list(L) ->
295
302
            Result;
296
 
%       Result ->
297
 
%           Result
298
303
        Error  ->
299
304
            parse_or(Tokens,Frest,[Error|ErrList])
300
305
    end.
301
306
 
 
307
parse_or_tag(Tokens,Flist) ->
 
308
        parse_or_tag(Tokens,Flist,[]).
 
309
 
 
310
parse_or_tag(_Tokens,[],ErrList) ->
 
311
    case ErrList of
 
312
        [] ->
 
313
            throw({asn1_error,{parse_or_tag,ErrList}});
 
314
        L when list(L) ->
 
315
            %% chose to throw 1) the error with the highest line no,
 
316
            %% 2) the last error which is not a asn1_assignment_error or
 
317
            %% 3) the last error.
 
318
            throw(prioritize_error(ErrList))
 
319
    end;
 
320
parse_or_tag(Tokens,[{Tag,Fun}|Frest],ErrList) when is_function(Fun) ->
 
321
    case (catch Fun(Tokens)) of
 
322
        Exit = {'EXIT',_Reason} ->
 
323
            parse_or_tag(Tokens,Frest,[Exit|ErrList]);
 
324
        AsnErr = {asn1_error,_} ->
 
325
            parse_or_tag(Tokens,Frest,[AsnErr|ErrList]);
 
326
        AsnAssErr = {asn1_assignment_error,_} ->
 
327
            parse_or_tag(Tokens,Frest,[AsnAssErr|ErrList]);
 
328
        {ParseRes,Rest} when list(Rest) ->
 
329
            {{Tag,ParseRes},Rest};
 
330
        Error  ->
 
331
            parse_or_tag(Tokens,Frest,[Error|ErrList])
 
332
    end.
 
333
 
302
334
parse_TypeAssignment([{typereference,L1,Tref},{'::=',_}|Rest]) ->       
303
335
    {Type,Rest2} = parse_Type(Rest),
304
336
    {#typedef{pos=L1,name=Tref,typespec=Type},Rest2};
444
476
    {#type{def='OCTET STRING'},Rest};
445
477
parse_BuiltinType([{'REAL',_}|Rest]) ->
446
478
    {#type{def='REAL'},Rest};
 
479
parse_BuiltinType([{'RELATIVE-OID',_}|Rest]) ->
 
480
    {#type{def='RELATIVE-OID'},Rest};
447
481
parse_BuiltinType([{'SEQUENCE',_},{'{',_},{'...',Line},{'}',_}|Rest]) ->
448
482
    {#type{def=#'SEQUENCE'{components=[{'EXTENSIONMARK',Line,undefined}]}},
449
483
     Rest};
821
855
            {[V1,intersection,V2],Rest2}
822
856
    end.
823
857
 
 
858
%% parse_IElemsRec(Tokens) -> Result
 
859
%% Result ::= {'SingleValue',ordered_set()} | list()
824
860
parse_IElemsRec([{'^',_}|Rest]) ->
825
861
    {InterSec,Rest2} = parse_IntersectionElements(Rest),
826
862
    {IRec,Rest3} = parse_IElemsRec(Rest2),
852
888
parse_IElemsRec(Tokens) ->
853
889
    {[],Tokens}.
854
890
 
 
891
%% parse_IntersectionElements(Tokens) -> {Result,Rest}
 
892
%% Result ::= InterSec | {InterSec,{'EXCEPT',Exclusion}}
 
893
%% InterSec ::= {'ALL',{'EXCEPT',Exclusions}} | Unions
 
894
%% Unions ::= {'SingleValue',list()} | list() (see parse_Unions)
 
895
%% Exclusions ::= InterSec
855
896
parse_IntersectionElements(Tokens) ->
856
897
    {InterSec,Rest} = parse_Elements(Tokens),
857
898
    case Rest of
862
903
            {InterSec,Rest}
863
904
    end.
864
905
 
 
906
%% parse_Elements(Tokens) -> {Result,Rest}
 
907
%% Result ::= {'ALL',{'EXCEPT',Exclusions}} | Unions
 
908
%% Exclusions ::= {'ALL',{'EXCEPT',Exclusions}} | Unions
 
909
%% Unions ::= {'SingleValue',list()} | list() (see parse_Unions)
865
910
parse_Elements([{'(',_}|Rest]) ->
866
911
    {Elems,Rest2} = parse_ElementSetSpec(Rest),
867
912
    case Rest2 of
1042
1087
    {OptionalitySpec,Rest3} = parse_ObjectOptionalitySpec(Rest2),
1043
1088
    case Rest3 of
1044
1089
        [{Del,_}|_] when Del =:= ','; Del =:= '}' ->
1045
 
            {{objectfield,VFieldName,Class,OptionalitySpec},Rest3};
 
1090
            {{objectfield,VFieldName,Class,undefined,OptionalitySpec},Rest3};
1046
1091
        _ ->
1047
1092
            throw({asn1_error,{L,get(asn1_module),
1048
1093
                           [got,get_token(hd(Rest3)),expected,[',','}']]}})
1379
1424
    end.
1380
1425
 
1381
1426
parse_Setting(Tokens) ->
1382
 
    Flist = [fun parse_Type/1,
1383
 
             fun parse_Value/1,
1384
 
             fun parse_Object/1,
1385
 
             fun parse_ObjectSet/1],
1386
 
    case (catch parse_or(Tokens,Flist)) of
 
1427
    Flist = [{type_tag,fun parse_Type/1},
 
1428
             {value_tag,fun parse_Value/1},
 
1429
             {object_tag,fun parse_Object/1},
 
1430
             {objectset_tag,fun parse_ObjectSet/1}],
 
1431
    case (catch parse_or_tag(Tokens,Flist)) of
1387
1432
        {'EXIT',Reason} ->
1388
1433
            exit(Reason);
1389
1434
        AsnErr = {asn1_error,_} ->
1390
1435
            throw(AsnErr);
1391
 
        Result ->
1392
 
            Result
 
1436
        Result = {{value_tag,_},_} ->
 
1437
            Result;
 
1438
        {{Tag,Setting},Rest} when is_atom(Tag) ->
 
1439
            {Setting,Rest}
1393
1440
    end.
1394
1441
 
 
1442
%% parse_Setting(Tokens) ->
 
1443
%%     Flist = [fun parse_Type/1,
 
1444
%%           fun parse_Value/1,
 
1445
%%           fun parse_Object/1,
 
1446
%%           fun parse_ObjectSet/1],
 
1447
%%     case (catch parse_or(Tokens,Flist)) of
 
1448
%%      {'EXIT',Reason} ->
 
1449
%%          exit(Reason);
 
1450
%%      AsnErr = {asn1_error,_} ->
 
1451
%%          throw(AsnErr);
 
1452
%%      Result ->
 
1453
%%          Result
 
1454
%%     end.
 
1455
 
1395
1456
parse_DefinedObjectSet([{typereference,L1,ModuleName},{'.',_},
1396
1457
                        {typereference,L2,ObjSetName}|Rest]) ->
1397
1458
    {{objectset,L1,#'Externaltypereference'{pos=L2,module=ModuleName,
1458
1519
    parse_ElementSetSpecs(Tokens).
1459
1520
 
1460
1521
% moved fun parse_Object/1 and fun parse_DefinedObjectSet/1 to parse_Elements
 
1522
%% parse_ObjectSetElements(Tokens) -> {Result,Rest}
 
1523
%% Result ::= {'ObjectSetFromObjects',Objects,Name} | {pos,ObjectSet,Params}
 
1524
%% Objects ::= ReferencedObjects
 
1525
%% ReferencedObjects ::= (see parse_ReferencedObjects/1)
 
1526
%% Name ::= [FieldName]
 
1527
%% FieldName ::= {typefieldreference,atom()} | {valuefieldreference,atom()}
 
1528
%% ObjectSet ::= {objectset,integer(),#'Externaltypereference'{}}
 
1529
%% Params ::= list() (see parse_ActualParameterList/1)
1461
1530
parse_ObjectSetElements(Tokens) ->
1462
1531
    Flist = [%fun parse_Object/1,
1463
1532
             %fun parse_DefinedObjectSet/1,
1531
1600
%           Result
1532
1601
%     end.
1533
1602
 
 
1603
%% parse_ReferencedObjects(Tokens) -> {Result,Rest}
 
1604
%% Result    ::= DefObject | DefObjSet |
 
1605
%%               {po,DefObject,Params} | {pos,DefObjSet,Params} |
 
1606
%%            
 
1607
%% DefObject ::= {object,#'Externaltypereference'{}} |
 
1608
%%               {object,#'Externalvaluereference'{}}
 
1609
%% DefObjSet ::= {objectset,integer(),#'Externaltypereference'{}}
 
1610
%% Params    ::= list()
1534
1611
parse_ReferencedObjects(Tokens) ->
1535
1612
    Flist = [fun parse_DefinedObject/1,
1536
1613
             fun parse_DefinedObjectSet/1,
1614
1691
        [H|_T] ->
1615
1692
            throw({asn1_error,{get_line(H),get(asn1_module),
1616
1693
                               [got,get_token(H),expected,'.']}})
1617
 
%%%     Other ->
1618
 
%%%         throw({asn1_error,{got,Other,expected,'.'}})
1619
1694
    end.
1620
1695
 
 
1696
%% parse_ObjectSetFromObjects(Tokens) -> {Result,Rest}
 
1697
%% Result  ::= {'ObjectSetFromObjects',Objects,Name}
 
1698
%% Objects ::= ReferencedObject (see parse_ReferencedObjects/1)
 
1699
%% Name    ::= [FieldName]
 
1700
%% FieldName ::= {typefieldreference,atom()} |
 
1701
%%               {valuefieldreference,atom()}
1621
1702
parse_ObjectSetFromObjects(Tokens) ->
1622
1703
    {Objects,Rest} = parse_ReferencedObjects(Tokens),
1623
1704
    case Rest of
1634
1715
        [H|_T] ->
1635
1716
            throw({asn1_error,{get_line(H),get(asn1_module),
1636
1717
                               [got,get_token(H),expected,'.']}})
1637
 
%%%     Other ->
1638
 
%%%         throw({asn1_error,{got,Other,expected,'.'}})
1639
1718
    end.
1640
1719
 
1641
1720
% parse_InstanceOfType([{'INSTANCE',_},{'OF',_}|Rest]) ->
2643
2722
    case Rest2 of
2644
2723
        [{'::=',_}|Rest3] ->
2645
2724
            {ValueSet,Rest4} = parse_ValueSet(Rest3),
2646
 
            {#valuedef{pos=L1,name=Name,type=Type,value=ValueSet},Rest4};
 
2725
            {#valuedef{pos=L1,name=Name,type=Type,value=ValueSet,
 
2726
                       module=get(asn1_module)},Rest4};
2647
2727
        [H|_T] ->
2648
2728
            throw({asn1_error,{get_line(L1),get(asn1_module),
2649
2729
                               [got,get_token(H),expected,'::=']}})
2673
2753
            {Value,Rest4} = parse_Value(Rest3),
2674
2754
            case catch lookahead_assignment(Rest4) of
2675
2755
                ok ->
2676
 
                    {#valuedef{pos=L1,name=IdName,type=Type,value=Value},Rest4};
 
2756
                    {#valuedef{pos=L1,name=IdName,type=Type,value=Value,
 
2757
                               module=get(asn1_module)},Rest4};
2677
2758
                Error ->
2678
2759
                    throw(Error)
2679
2760
%%                  throw({asn1_error,{get_line(hd(Rest2)),get(asn1_module),