~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1ct_constructed_per.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2010. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%%
46
46
    asn1ct_name:start(),
47
47
    asn1ct_name:new(term),
48
48
    asn1ct_name:new(bytes),
49
 
    {CompList,TableConsInfo} = 
 
49
    {ExtAddGroup,TmpCompList,TableConsInfo} =
50
50
        case D#type.def of
51
 
            #'SEQUENCE'{tablecinf=TCI,components=CL} ->
52
 
                {CL,TCI};
 
51
            #'SEQUENCE'{tablecinf=TCI,components=CL,extaddgroup=ExtAddGroup0} ->
 
52
                {ExtAddGroup0,CL,TCI};
53
53
            #'SET'{tablecinf=TCI,components=CL} ->
54
 
                {CL,TCI}
 
54
                {undefined,CL,TCI}
55
55
        end,
 
56
 
 
57
    CompList = case ExtAddGroup of
 
58
                   undefined ->
 
59
                       TmpCompList;
 
60
                   _ when is_integer(ExtAddGroup) ->
 
61
                       %% This is a fake SEQUENCE representing an ExtensionAdditionGroup
 
62
                       %% Reset the textual order so we get the right
 
63
                       %% index of the components
 
64
                       [Comp#'ComponentType'{textual_order=undefined}||
 
65
                           Comp<-TmpCompList]
 
66
               end,
56
67
    case Typename of
57
68
        ['EXTERNAL'] ->
58
 
            emit({{var,asn1ct_name:next(val)},
 
69
            emit({{next,val},
59
70
                  " = asn1rt_check:transform_to_EXTERNAL1990(",
60
 
                  {var,asn1ct_name:curr(val)},"),",nl}),
 
71
                  {curr,val},"),",nl}),
61
72
            asn1ct_name:new(val);
62
73
        _ ->
63
74
            ok
66
77
        {[],EmptyCL} when EmptyCL == {[],[],[]};EmptyCL == {[],[]};EmptyCL == [] -> 
67
78
            emit(["%%Variable setting just to eliminate ",
68
79
                  "compiler warning for unused vars!",nl,
69
 
                  "_Val = ",{var,asn1ct_name:curr(val)},",",nl]);
 
80
                  "_Val = ",{curr,val},",",nl]);
70
81
        {[],_} ->
71
 
            emit([{var,asn1ct_name:next(val)}," = ?RT_PER:list_to_record("]),
 
82
            emit([{next,val}," = ?RT_PER:list_to_record("]),
72
83
            emit(["'",asn1ct_gen:list2rname(Typename),"'"]),
73
 
            emit([", ",{var,asn1ct_name:curr(val)},"),",nl]);
 
84
            emit([", ",{curr,val},"),",nl]);
74
85
        _ ->
75
86
            Fixoptcall = ",Opt} = ?RT_PER:fixoptionals(",
76
 
            emit({"{",{var,asn1ct_name:next(val)},Fixoptcall,
 
87
            emit({"{",{next,val},Fixoptcall,
77
88
                  {asis,Optionals},",",length(Optionals),
78
 
                  ",",{var,asn1ct_name:curr(val)},"),",nl})
 
89
                  ",",{curr,val},"),",nl})
79
90
    end,
80
91
    asn1ct_name:new(val),
81
 
    Ext = extensible(CompList),
 
92
    Ext = extensible_enc(CompList),
82
93
    case Ext of
83
94
        {ext,_,NumExt} when NumExt > 0 ->
84
 
            emit(["Extensions = ?RT_PER:fixextensions(",{asis,Ext},
85
 
                  ", ",{curr,val},"),",nl]);
 
95
            case extgroup_pos_and_length(CompList) of
 
96
                {extgrouppos,ExtGroupPos,ExtGroupLen} ->
 
97
                    Elements = make_elements(ExtGroupPos+1,
 
98
                                             "Val1",lists:seq(1,ExtGroupLen)),
 
99
                    emit([
 
100
                          {next,val}," = case [X || X <- [",Elements,
 
101
                          "],X =/= asn1_NOVALUE] of",nl,
 
102
                          "[] -> ",{curr,val},";",nl,
 
103
                          "_ -> setelement(",{asis,ExtGroupPos+1},",",
 
104
                          {curr,val},",",
 
105
                          "{extaddgroup,", Elements,"})",nl,
 
106
                          "end,",nl]),
 
107
                    asn1ct_name:new(val);
 
108
                _ -> % no extensionAdditionGroup
 
109
                    ok
 
110
            end,
 
111
            asn1ct_name:new(tmpval),
 
112
            emit(["Extensions = ?RT_PER:fixextensions(",{asis,Ext},",",
 
113
                  {curr,val},"),",nl]);
86
114
        _ -> true
87
115
    end,
88
116
    EncObj =
188
216
            #'SEQUENCE'{tablecinf=TCI,components=CL} ->
189
217
                {add_textual_order(CL),TCI};
190
218
            #'SET'{tablecinf=TCI,components=CL} ->
191
 
                {add_textual_order(CL),TCI}
 
219
%%              {add_textual_order(CL),TCI}
 
220
                {CL,TCI} % the textual order is already taken care of
192
221
        end,
193
 
    Ext = extensible(CompList),
 
222
    Ext = extensible_dec(CompList),
194
223
    MaybeComma1 = case Ext of
195
224
                      {ext,_Pos,_NumExt} -> 
196
225
                          gen_dec_extension_value("Bytes"),
243
272
                        {false,false,false}
244
273
                end
245
274
        end,
 
275
    NewCompList = wrap_compList(CompList),
246
276
    {AccTerm,AccBytes} =
247
 
        gen_dec_components_call(Erules,Typename,CompList,MaybeComma2,DecObjInf,Ext,length(Optionals)),
 
277
        gen_dec_components_call(Erules,Typename,NewCompList,MaybeComma2,DecObjInf,Ext,length(Optionals)),
248
278
    case asn1ct_name:all(term) of
249
279
        [] -> emit(MaybeComma2); % no components at all
250
280
        _ -> emit({com,nl})
284
314
            emit("   {ASN11994Format,");
285
315
        _ ->
286
316
            emit(["{{'",RecordName,"'"]),
287
 
            mkvlist(textual_order(CompList,asn1ct_name:all(term))),
 
317
            %% CompList is used here because we don't want
 
318
            %% ExtensionAdditionGroups to be wrapped in SEQUENCES when
 
319
            %% we are ordering the fields according to textual order
 
320
            mkvlist(textual_order(to_encoding_order(CompList),asn1ct_name:all(term))),
288
321
            emit("},")
289
322
    end,
290
 
    emit({{var,asn1ct_name:curr(bytes)},"}"}),
 
323
    emit({{curr,bytes},"}"}),
291
324
    emit({".",nl,nl}).
292
325
 
293
326
textual_order([#'ComponentType'{textual_order=undefined}|_],TermList) ->
294
327
    TermList;
295
328
textual_order(CompList,TermList) when is_list(CompList) ->
296
 
    TermTuple = list_to_tuple(TermList), %% ['Term1','Term2',...'TermN']
297
 
    %% OrderList is ordered by canonical order of tags
298
 
    TmpTuple = TermTuple,
299
 
    OrderList = [Ix||#'ComponentType'{textual_order=Ix} <- CompList], 
300
 
    Fun = fun(X,{Tpl,Ix}) ->
301
 
                  
302
 
                  {setelement(X,Tpl,element(Ix,TermTuple)),Ix+1}
303
 
          end,
304
 
    {Ret,_} = lists:foldl(Fun,{TmpTuple,1},OrderList),
305
 
%%    io:format("TermTuple: ~p~nOrderList: ~p~nRet: ~p~n",[TermTuple,OrderList,tuple_to_list(Ret)]),
306
 
    tuple_to_list(Ret);
 
329
    OrderList = [Ix||#'ComponentType'{textual_order=Ix} <- CompList],
 
330
    [Term||{_,Term}<-
 
331
               lists:sort(lists:zip(OrderList,
 
332
                                    lists:sublist(TermList,length(OrderList))))];
 
333
               %% sublist is just because Termlist can sometimes be longer than
 
334
               %% OrderList, which it really shouldn't
307
335
textual_order({Root,Ext},TermList) ->
308
 
    textual_order(Root ++ Ext,TermList);
309
 
textual_order({Root1,Ext,Root2},TermList) ->
310
 
    textual_order(Root1 ++ Ext ++ Root2, TermList).
 
336
    textual_order(Root ++ Ext,TermList).
311
337
 
312
338
to_textual_order({Root,Ext}) ->
313
339
    {to_textual_order(Root),Ext};
379
405
gen_encode_choice(Erule,Typename,D) when is_record(D,type) ->
380
406
    {'CHOICE',CompList} = D#type.def,
381
407
    emit({"[",nl}),
382
 
    Ext = extensible(CompList),
 
408
    Ext = extensible_enc(CompList),
383
409
    gen_enc_choice(Erule,Typename,CompList,Ext),
384
410
    emit({nl,"].",nl}).
385
411
 
388
414
    asn1ct_name:clear(),
389
415
    asn1ct_name:new(bytes),
390
416
    {'CHOICE',CompList} = D#type.def,
391
 
    Ext = extensible(CompList),
 
417
    Ext = extensible_enc(CompList),
392
418
    gen_dec_choice(Erules,Typename,CompList,Ext),
393
419
    emit({".",nl}).
394
420
 
558
584
mkvlist2([]) ->
559
585
    true.
560
586
 
561
 
extensible(CompList) when is_list(CompList) ->
562
 
    noext;
563
 
extensible({RootList,ExtList}) ->
564
 
    {ext,length(RootList)+1,length(ExtList)};
565
 
extensible({Rl1,Ext,_Rl2}) ->
566
 
     {ext,length(Rl1)+1,length(Ext)}.
 
587
 
 
588
extensible_dec(CompList) when is_list(CompList) ->
 
589
    noext;
 
590
extensible_dec({RootList,ExtList}) ->
 
591
    {ext,length(RootList)+1,ext_length(ExtList)};
 
592
extensible_dec({Rl1,Ext,Rl2}) ->
 
593
     {ext,length(Rl1)+length(Rl2)+1,ext_length(Ext)}.
 
594
 
 
595
extensible_enc(CompList) when is_list(CompList) ->
 
596
    noext;
 
597
extensible_enc({RootList,ExtList}) ->
 
598
    {ext,length(RootList)+1,ext_length(ExtList)};
 
599
extensible_enc({Rl1,Ext,_Rl2}) ->
 
600
     {ext,length(Rl1)+1,ext_length(Ext)}.
 
601
 
 
602
ext_length(ExtList) -> ext_length(ExtList,normal,0).
 
603
ext_length([{'ExtensionAdditionGroup',_Num}|T],_,Acc)->
 
604
    ext_length(T,group,Acc);
 
605
ext_length(['ExtensionAdditionGroupEnd'|T],group,Acc) ->
 
606
    ext_length(T,normal,Acc+1);
 
607
ext_length([#'ComponentType'{}|T],State=group,Acc) ->
 
608
    ext_length(T,State,Acc);
 
609
ext_length([#'ComponentType'{}|T],State=normal,Acc) ->
 
610
    ext_length(T,State,Acc+1);
 
611
ext_length([],_,Acc) ->
 
612
    Acc.
 
613
 
 
614
extgroup_pos_and_length(CompList) when is_list(CompList) ->
 
615
    noextgroup;
 
616
extgroup_pos_and_length({RootList,ExtList}) ->
 
617
    extgrouppos(ExtList,length(RootList)+1);
 
618
extgroup_pos_and_length({Rl1,Ext,_Rl2}) ->
 
619
    extgrouppos(Ext,length(Rl1)+1).
 
620
 
 
621
extgrouppos([{'ExtensionAdditionGroup',_Num}|T],Pos) ->
 
622
    extgrouppos(T,Pos,0);
 
623
extgrouppos([_|T],Pos) ->
 
624
    extgrouppos(T,Pos+1);
 
625
extgrouppos([],_) ->
 
626
    noextgroup.
 
627
 
 
628
extgrouppos(['ExtensionAdditionGroupEnd'|_T],Pos,Len) ->
 
629
    {extgrouppos,Pos,Len};
 
630
extgrouppos([_|T],Pos,Len) ->
 
631
    extgrouppos(T,Pos,Len+1).
 
632
    
 
633
 
567
634
 
568
635
gen_dec_extension_value(_) ->
569
636
    emit({"{Ext,",{next,bytes},"} = ?RT_PER:getext(",{curr,bytes},")"}),
574
641
%% there are optional components, start with 2 because first element
575
642
%% is the record name
576
643
 
577
 
optionals({L1,_Ext,L2}) -> optionals(L1++L2,[],2); 
 
644
optionals({L1,Ext,L2}) ->
 
645
    Opt1 = optionals(L1,[],2),
 
646
    ExtComps = length([C||C = #'ComponentType'{}<-Ext]),
 
647
    Opt2 = optionals(L2,[],2+length(L1)+ExtComps),
 
648
    Opt1 ++ Opt2;
578
649
optionals({L,_Ext}) -> optionals(L,[],2); 
579
650
optionals(L) -> optionals(L,[],2).
580
651
 
617
688
            no_num
618
689
    end.
619
690
 
 
691
to_encoding_order(Cs) when is_list(Cs) ->
 
692
    Cs;
 
693
to_encoding_order(Cs = {_Root,_Ext}) ->
 
694
    Cs;
 
695
to_encoding_order({R1,Ext,R2}) ->
 
696
    {R1++R2,Ext}.
 
697
 
620
698
add_textual_order(Cs) when is_list(Cs) ->
621
699
    {NewCs,_} = add_textual_order1(Cs,1),
622
700
    NewCs;
629
707
    {NewExt,Num2} = add_textual_order1(Ext,Num1),
630
708
    {NewR2,_} = add_textual_order1(R2,Num2),
631
709
    {NewR1,NewExt,NewR2}.
632
 
add_textual_order1(Cs=[#'ComponentType'{textual_order=Int}|_],I)
633
 
  when is_integer(Int) ->
634
 
    {Cs,I};
 
710
%%add_textual_order1(Cs=[#'ComponentType'{textual_order=Int}|_],I)
 
711
%%  when is_integer(Int) ->
 
712
%%    {Cs,I};
635
713
add_textual_order1(Cs,NumIn) ->
636
 
    lists:mapfoldl(fun(C,Num) ->
 
714
    lists:mapfoldl(fun(C=#'ComponentType'{},Num) ->
637
715
                           {C#'ComponentType'{textual_order=Num},
638
 
                            Num+1}
 
716
                            Num+1};
 
717
                      (OtherMarker,Num) ->
 
718
                           {OtherMarker,Num}
639
719
                   end,
640
720
                   NumIn,Cs).
641
721
 
642
722
gen_enc_components_call(Erule,TopType,{Root1,ExtList,Root2},MaybeComma,DynamicEnc,Ext) ->
643
 
    Rpos = gen_enc_components_call1(Erule,TopType,Root1,1,MaybeComma,DynamicEnc,noext),
644
 
    case Ext of
645
 
        {ext,_,ExtNum} when ExtNum > 0 ->
646
 
            emit([nl,
647
 
                  ",Extensions",nl]);
648
 
        _ -> true
649
 
    end,
650
 
    Rpos2 = gen_enc_components_call1(Erule,TopType,ExtList,Rpos,MaybeComma,DynamicEnc,Ext),
651
 
    gen_enc_components_call1(Erule,TopType,Root2,Rpos2,MaybeComma,DynamicEnc,noext);
 
723
    gen_enc_components_call(Erule,TopType,{Root1++Root2,ExtList},MaybeComma,DynamicEnc,Ext);
652
724
gen_enc_components_call(Erule,TopType,{CompList,ExtList},MaybeComma,DynamicEnc,Ext) ->
653
725
    %% The type has extensionmarker
654
726
    Rpos = gen_enc_components_call1(Erule,TopType,CompList,1,MaybeComma,DynamicEnc,noext),
659
731
        _ -> true
660
732
    end,
661
733
    %handle extensions
662
 
    gen_enc_components_call1(Erule,TopType,ExtList,Rpos,MaybeComma,DynamicEnc,Ext);
 
734
    NewExtList = wrap_extensionAdditionGroups(ExtList),
 
735
    gen_enc_components_call1(Erule,TopType,NewExtList,Rpos,MaybeComma,DynamicEnc,Ext);
663
736
gen_enc_components_call(Erule,TopType, CompList, MaybeComma, DynamicEnc, Ext) ->
664
737
    %% The type has no extensionmarker
665
738
    gen_enc_components_call1(Erule,TopType,CompList,1,MaybeComma,DynamicEnc,Ext).
706
779
        Pos.
707
780
 
708
781
gen_enc_component_default(Erule,TopType,Cname,Type,Pos,DynamicEnc,Ext,DefaultVal) ->
709
 
    Element = make_element(Pos+1,"Val1",Cname),
 
782
    Element = make_element(Pos+1,asn1ct_gen:mk_var(asn1ct_name:curr(val)),Cname),
710
783
    emit({"case ",Element," of",nl}),
711
784
%    emit({"asn1_DEFAULT -> [];",nl}),
712
785
    emit({"DFLT when DFLT == asn1_DEFAULT; DFLT == ",{asis,DefaultVal}," -> [];",nl}),
719
792
    NextElement = asn1ct_gen:mk_var(asn1ct_name:curr(tmpval)),
720
793
    gen_enc_line(Erule,TopType,Cname,Type,NextElement, Pos,DynamicEnc,Ext),
721
794
    emit({nl,"end"}).
 
795
 
 
796
gen_enc_component_optional(Erule,TopType,Cname,
 
797
                           Type=#type{def=#'SEQUENCE'{
 
798
                                        extaddgroup=Number,
 
799
                                        components=_ExtGroupCompList}},
 
800
                           Pos,DynamicEnc,Ext) when is_integer(Number) ->
 
801
 
 
802
    Element = make_element(Pos+1,asn1ct_gen:mk_var(asn1ct_name:curr(val)),Cname),
 
803
    emit({"case ",Element," of",nl}),
 
804
 
 
805
    emit({"asn1_NOVALUE -> [];",nl}),
 
806
    asn1ct_name:new(tmpval),
 
807
    emit({{curr,tmpval}," ->",nl}),
 
808
    InnerType = asn1ct_gen:get_inner(Type#type.def),
 
809
    emit({nl,"%% attribute number ",Pos," with type ",
 
810
              InnerType,nl}),
 
811
    NextElement = asn1ct_gen:mk_var(asn1ct_name:curr(tmpval)),
 
812
    gen_enc_line(Erule,TopType,Cname,Type,NextElement, Pos,DynamicEnc,Ext),
 
813
    emit({nl,"end"});
722
814
gen_enc_component_optional(Erule,TopType,Cname,Type,Pos,DynamicEnc,Ext) ->
723
 
    Element = make_element(Pos+1,"Val1",Cname),
 
815
    Element = make_element(Pos+1,asn1ct_gen:mk_var(asn1ct_name:curr(val)),Cname),
724
816
    emit({"case ",Element," of",nl}),
725
817
 
726
818
    emit({"asn1_NOVALUE -> [];",nl}),
834
926
        _ -> true
835
927
    end.
836
928
gen_dec_components_call(Erule,TopType,{Root1,ExtList,Root2},MaybeComma,DecInfObj,Ext,NumberOfOptionals) ->
837
 
     %% The type has extensionmarker
838
 
     OptTable = create_optionality_table(Root1 ++ Root2),
839
 
     {Rpos,AccTerm,AccBytes} = 
840
 
        gen_dec_components_call1(Erule,TopType, Root1, 1, OptTable,
841
 
                                 MaybeComma,DecInfObj, noext,[],[],
842
 
                                 NumberOfOptionals),
843
 
     emit([",",nl,"{Extensions,",{next,bytes},"} = "]),
844
 
     emit(["?RT_PER:getextension(Ext,",{curr,bytes},"),",nl]),
845
 
     asn1ct_name:new(bytes),
846
 
     {Epos,AccTermE,AccBytesE} = 
847
 
        gen_dec_components_call1(Erule,TopType,ExtList,Rpos, OptTable, "",
848
 
                                 DecInfObj,Ext,[],[],NumberOfOptionals),
849
 
     case ExtList of
850
 
        [] -> true;
851
 
        _ -> emit([",",nl])
852
 
     end,
853
 
     emit([{next,bytes},"= ?RT_PER:skipextensions(",{curr,bytes},",",
854
 
          length(ExtList)+1,",Extensions),",nl]),
855
 
     asn1ct_name:new(bytes),
856
 
     {_RPos2,AccTerm2,AccBytes2} =
857
 
        gen_dec_components_call1(Erule,TopType,Root2,Epos,OptTable,
858
 
                                 "",DecInfObj,noext,[],[],NumberOfOptionals),
859
 
     {AccTerm++AccTermE++AccTerm2,AccBytes++AccBytesE++AccBytes2};
 
929
    gen_dec_components_call(Erule,TopType,{Root1++Root2,ExtList},MaybeComma,DecInfObj,Ext,NumberOfOptionals);
860
930
gen_dec_components_call(Erule,TopType,{CompList,ExtList},MaybeComma,
861
931
                        DecInfObj,Ext,NumberOfOptionals) ->
862
932
    %% The type has extensionmarker
868
938
    emit([",",nl,"{Extensions,",{next,bytes},"} = "]),
869
939
    emit(["?RT_PER:getextension(Ext,",{curr,bytes},"),",nl]),
870
940
    asn1ct_name:new(bytes),
 
941
    NewExtList = wrap_extensionAdditionGroups(ExtList),
871
942
    {_Epos,AccTermE,AccBytesE} = 
872
 
        gen_dec_components_call1(Erule,TopType,ExtList,Rpos, OptTable,
 
943
        gen_dec_components_call1(Erule,TopType,NewExtList,Rpos, OptTable,
873
944
                                 "",DecInfObj,Ext,[],[],NumberOfOptionals),
874
945
    case ExtList of
875
946
        [] -> true;
942
1013
            asn1ct_name:new(tmpterm),
943
1014
            emit({"{",{curr,tmpterm},", ",{next,bytes},"} = "});
944
1015
        _ ->
945
 
            asn1ct_name:new(term),
946
 
            emit({"{",{curr,term},",",{next,bytes},"} = "})
 
1016
            case Type of
 
1017
                #type{def=#'SEQUENCE'{
 
1018
                        extaddgroup=Number1,
 
1019
                        components=ExtGroupCompList1}} when is_integer(Number1)->
 
1020
                    emit({"{{_,"}),
 
1021
                    emit_extaddgroupTerms(term,ExtGroupCompList1),
 
1022
                    emit({"}"});
 
1023
                _ ->
 
1024
                    asn1ct_name:new(term),
 
1025
                    emit({"{",{curr,term}})
 
1026
            end,
 
1027
            emit({",",{next,bytes},"} = "})
947
1028
    end,
948
1029
 
949
1030
    case {Ext,Prop,is_optimized(Erule)} of
967
1048
        {noext,mandatory} -> true; % generate nothing
968
1049
        {noext,_} ->
969
1050
            emit([";",nl,"0 ->"]),
970
 
            gen_dec_component_no_val(TopType,Cname,Type,Prop,Tpos,Ext),
 
1051
            emit(["{"]),
 
1052
            gen_dec_component_no_val(Ext,Prop),
 
1053
            emit({",",{curr,bytes},"}",nl}),
971
1054
            emit([nl,"end"]);
972
1055
        _ ->
973
1056
            emit([";",nl,"_  ->",nl]),
974
 
            gen_dec_component_no_val(TopType,Cname,Type,Prop,Tpos,Ext),
 
1057
            emit(["{"]),
 
1058
            case Type of
 
1059
                #type{def=#'SEQUENCE'{
 
1060
                        extaddgroup=Number2,
 
1061
                        components=ExtGroupCompList2}} when is_integer(Number2)->
 
1062
                    emit({"{extAddGroup,"}),
 
1063
                    gen_dec_extaddGroup_no_val(Ext,ExtGroupCompList2),
 
1064
                    emit({"}"});
 
1065
                _ ->
 
1066
                    gen_dec_component_no_val(Ext,Prop)
 
1067
            end,
 
1068
            emit({",",{curr,bytes},"}",nl}),
975
1069
            emit([nl,"end"])
976
1070
    end,    
977
1071
    asn1ct_name:new(bytes),
988
1082
gen_dec_components_call1(_,_TopType,[],Pos,_OptTable,_,_,_,AccTerm,AccBytes,_NumberOfOptionals) ->
989
1083
    {Pos,AccTerm,AccBytes}.
990
1084
 
 
1085
gen_dec_extaddGroup_no_val(Ext,[#'ComponentType'{prop=Prop}])->
 
1086
    gen_dec_component_no_val(Ext,Prop),
 
1087
    ok;
 
1088
gen_dec_extaddGroup_no_val(Ext,[#'ComponentType'{prop=Prop}|Rest])->
 
1089
    gen_dec_component_no_val(Ext,Prop),
 
1090
    emit({","}),
 
1091
    gen_dec_extaddGroup_no_val(Ext,Rest);
 
1092
gen_dec_extaddGroup_no_val(_, []) ->
 
1093
    ok.
991
1094
 
992
 
gen_dec_component_no_val(_,_,_,{'DEFAULT',DefVal},_,_) ->
993
 
    emit(["{",{asis,DefVal},",",{curr,bytes},"}",nl]);
994
 
gen_dec_component_no_val(_,_,_,'OPTIONAL',_,_) ->
995
 
    emit({"{asn1_NOVALUE,",{curr,bytes},"}",nl});
996
 
gen_dec_component_no_val(_,_,_,mandatory,_,{ext,_,_}) ->
997
 
    emit({"{asn1_NOVALUE,",{curr,bytes},"}",nl}).
 
1095
gen_dec_component_no_val(_,{'DEFAULT',DefVal}) ->
 
1096
    emit([{asis,DefVal}]);
 
1097
gen_dec_component_no_val(_,'OPTIONAL') ->
 
1098
    emit({"asn1_NOVALUE"});
 
1099
gen_dec_component_no_val({ext,_,_},mandatory) ->
 
1100
    emit({"asn1_NOVALUE"}).
998
1101
    
999
1102
 
1000
1103
gen_dec_line(Erule,TopType,Cname,Type,Pos,DecInfObj,Ext,Prop)  ->
1192
1295
    N2 = get_name_list(C2),
1193
1296
    emit(["?RT_PER:set_choice(element(1,Val),",
1194
1297
          {asis,{N1,N2}},", ",{asis,{length(N1),length(N2)}},")"]);
 
1298
 
 
1299
gen_enc_choice_tag({C1,C2,C3},_,_) ->
 
1300
    N1 = get_name_list(C1),
 
1301
    N2 = get_name_list(C2),
 
1302
    N3 = get_name_list(C3),
 
1303
    Root = N1 ++ N3,
 
1304
    emit(["?RT_PER:set_choice(element(1,Val),",
 
1305
          {asis,{Root,N2}},", ",{asis,{length(Root),length(N2)}},")"]);
1195
1306
gen_enc_choice_tag(C,_,_) ->
1196
1307
    N = get_name_list(C),
1197
1308
    emit(["?RT_PER:set_choice(element(1,Val),",
1208
1319
 
1209
1320
gen_enc_choice2(Erule,TopType, {L1,L2}, Ext) ->
1210
1321
    gen_enc_choice2(Erule,TopType, L1 ++ L2, 0, Ext);
 
1322
gen_enc_choice2(Erule,TopType, {L1,L2,L3}, Ext) ->
 
1323
    gen_enc_choice2(Erule,TopType, L1 ++ L3 ++ L2, 0, Ext);
1211
1324
gen_enc_choice2(Erule,TopType, L, Ext) ->
1212
1325
    gen_enc_choice2(Erule,TopType, L, 0, Ext).
1213
1326
 
1279
1392
gen_dec_choice1(Erule,TopType,{RootList,ExtList},Ext) ->
1280
1393
    NewList = RootList ++ ExtList,
1281
1394
    gen_dec_choice1(Erule,TopType, NewList, Ext);
 
1395
gen_dec_choice1(Erule,TopType,{RootList,ExtList,RootList2},Ext) ->
 
1396
    NewList = RootList ++ RootList2 ++ ExtList,
 
1397
    gen_dec_choice1(Erule,TopType, NewList, Ext);
1282
1398
gen_dec_choice1(Erule,TopType,CompList,{ext,ExtPos,ExtNum}) ->
1283
1399
    emit({"{Choice,",{curr,bytes},
1284
1400
          "} = ?RT_PER:getchoice(",{prev,bytes},",",
1347
1463
    CtgenMod:gen_encode_prim(Erule,Cont,DoTag,Value).
1348
1464
%    erase(component_type).
1349
1465
 
 
1466
make_elements(I,Val,ExtCnames) ->
 
1467
    make_elements(I,Val,ExtCnames,[]).
 
1468
 
 
1469
make_elements(I,Val,[ExtCname],Acc)-> % the last one, no comma needed
 
1470
    Element = make_element(I,Val,ExtCname),
 
1471
    make_elements(I+1,Val,[],[Element|Acc]);
 
1472
make_elements(I,Val,[ExtCname|Rest],Acc)->
 
1473
    Element = make_element(I,Val,ExtCname),
 
1474
    make_elements(I+1,Val,Rest,[", ",Element|Acc]);
 
1475
make_elements(_I,_,[],Acc) ->
 
1476
    lists:reverse(Acc).
 
1477
 
1350
1478
make_element(I,Val,Cname) ->
1351
1479
    case tuple_notation_allowed() of
1352
1480
        true ->
1355
1483
            io_lib:format("element(~w,~s)",[I,Val])
1356
1484
    end.
1357
1485
 
 
1486
emit_extaddgroupTerms(VarSeries,[_]) ->
 
1487
    asn1ct_name:new(VarSeries),
 
1488
    emit({curr,VarSeries}),
 
1489
    ok;
 
1490
emit_extaddgroupTerms(VarSeries,[_|Rest]) ->
 
1491
    asn1ct_name:new(VarSeries),
 
1492
    emit({{curr,VarSeries},","}),
 
1493
    emit_extaddgroupTerms(VarSeries,Rest);
 
1494
emit_extaddgroupTerms(_,[]) ->
 
1495
    ok.
 
1496
wrap_compList({Root1,Ext,Root2}) ->
 
1497
    {Root1,wrap_extensionAdditionGroups(Ext),Root2};
 
1498
wrap_compList({Root1,Ext}) ->
 
1499
    {Root1,wrap_extensionAdditionGroups(Ext)};
 
1500
wrap_compList(CompList) ->
 
1501
    CompList.
 
1502
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1503
%%  Will convert all componentTypes following 'ExtensionAdditionGroup'
 
1504
%%  up to the matching 'ExtensionAdditionGroupEnd' into one componentType
 
1505
%% of type SEQUENCE with the componentTypes as components
 
1506
%%
 
1507
wrap_extensionAdditionGroups(ExtCompList) ->
 
1508
    wrap_extensionAdditionGroups(ExtCompList,[],0).
 
1509
 
 
1510
wrap_extensionAdditionGroups([{'ExtensionAdditionGroup',_Number}|Rest],Acc,0) ->
 
1511
    {ExtGroupCompList=
 
1512
     [#'ComponentType'{textual_order=TextPos}|_],
 
1513
     ['ExtensionAdditionGroupEnd'|Rest2]} =
 
1514
        lists:splitwith(fun(#'ComponentType'{}) -> true;
 
1515
                           (_) -> false
 
1516
                        end,
 
1517
                        Rest),
 
1518
    wrap_extensionAdditionGroups(Rest2,
 
1519
                                 [#'ComponentType'{
 
1520
                                  name='ExtAddGroup', % FIXME: handles ony one ExtAddGroup
 
1521
                                  typespec=#type{def=#'SEQUENCE'{
 
1522
                                                   extaddgroup=1,% FIXME: handles only one
 
1523
                                                   components=ExtGroupCompList}},
 
1524
                                  textual_order = TextPos,
 
1525
                                  prop='OPTIONAL'}|Acc],length(ExtGroupCompList)-1);
 
1526
wrap_extensionAdditionGroups([H=#'ComponentType'{textual_order=Tord}|T],Acc,ExtAddGroupDiff) when is_integer(Tord) ->
 
1527
    wrap_extensionAdditionGroups(T,[H#'ComponentType'{
 
1528
                                      textual_order=Tord - ExtAddGroupDiff}|Acc],ExtAddGroupDiff);
 
1529
wrap_extensionAdditionGroups([H|T],Acc,ExtAddGroupDiff) ->
 
1530
    wrap_extensionAdditionGroups(T,[H|Acc],ExtAddGroupDiff);
 
1531
wrap_extensionAdditionGroups([],Acc,_) ->
 
1532
    lists:reverse(Acc).
 
1533
 
 
1534
 
1358
1535
tuple_notation_allowed() ->
1359
1536
    Options = get(encoding_options),
1360
1537
    not (lists:member(optimize,Options) orelse lists:member(uper_bin,Options)).