aboutsummaryrefslogtreecommitdiffstats
path: root/lib/asn1/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/asn1/src')
-rw-r--r--lib/asn1/src/asn1ct.erl22
-rw-r--r--lib/asn1/src/asn1ct_check.erl72
-rw-r--r--lib/asn1/src/asn1ct_constructed_per.erl63
-rw-r--r--lib/asn1/src/asn1ct_gen_ber_bin_v2.erl19
-rw-r--r--lib/asn1/src/asn1ct_gen_per.erl164
-rw-r--r--lib/asn1/src/asn1ct_gen_per_rt2ct.erl189
-rw-r--r--lib/asn1/src/asn1ct_parser2.erl31
-rw-r--r--lib/asn1/src/asn1rt_uper_bin.erl15
8 files changed, 224 insertions, 351 deletions
diff --git a/lib/asn1/src/asn1ct.erl b/lib/asn1/src/asn1ct.erl
index 90882462ac..98877320a0 100644
--- a/lib/asn1/src/asn1ct.erl
+++ b/lib/asn1/src/asn1ct.erl
@@ -1288,35 +1288,35 @@ pretty2(Module,AbsFile) ->
{ok,F} = file:open(AbsFile,[write]),
M = asn1_db:dbget(Module,'MODULE'),
io:format(F,"%%%%%%%%%%%%%%%%%%% ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- io:format(F,"~s\n",[asn1ct_pretty_format:term(M#module.defid)]),
- io:format(F,"~s\n",[asn1ct_pretty_format:term(M#module.tagdefault)]),
- io:format(F,"~s\n",[asn1ct_pretty_format:term(M#module.exports)]),
- io:format(F,"~s\n",[asn1ct_pretty_format:term(M#module.imports)]),
- io:format(F,"~s\n\n",[asn1ct_pretty_format:term(M#module.extensiondefault)]),
+ io:format(F,"~s.\n",[asn1ct_pretty_format:term(M#module.defid)]),
+ io:format(F,"~s.\n",[asn1ct_pretty_format:term(M#module.tagdefault)]),
+ io:format(F,"~s.\n",[asn1ct_pretty_format:term(M#module.exports)]),
+ io:format(F,"~s.\n",[asn1ct_pretty_format:term(M#module.imports)]),
+ io:format(F,"~s.\n\n",[asn1ct_pretty_format:term(M#module.extensiondefault)]),
{Types,Values,ParameterizedTypes,Classes,Objects,ObjectSets} = M#module.typeorval,
io:format(F,"%%%%%%%%%%%%%%%%%%% TYPES in ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- lists:foreach(fun(T)-> io:format(F,"~s\n",
+ lists:foreach(fun(T)-> io:format(F,"~s.\n",
[asn1ct_pretty_format:term(asn1_db:dbget(Module,T))])
end,Types),
io:format(F,"%%%%%%%%%%%%%%%%%%% VALUES in ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- lists:foreach(fun(T)-> io:format(F,"~s\n",
+ lists:foreach(fun(T)-> io:format(F,"~s.\n",
[asn1ct_pretty_format:term(asn1_db:dbget(Module,T))])
end,Values),
io:format(F,"%%%%%%%%%%%%%%%%%%% Parameterized Types in ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- lists:foreach(fun(T)-> io:format(F,"~s\n",
+ lists:foreach(fun(T)-> io:format(F,"~s.\n",
[asn1ct_pretty_format:term(asn1_db:dbget(Module,T))])
end,ParameterizedTypes),
io:format(F,"%%%%%%%%%%%%%%%%%%% Classes in ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- lists:foreach(fun(T)-> io:format(F,"~s\n",
+ lists:foreach(fun(T)-> io:format(F,"~s.\n",
[asn1ct_pretty_format:term(asn1_db:dbget(Module,T))])
end,Classes),
io:format(F,"%%%%%%%%%%%%%%%%%%% Objects in ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- lists:foreach(fun(T)-> io:format(F,"~s\n",
+ lists:foreach(fun(T)-> io:format(F,"~s.\n",
[asn1ct_pretty_format:term(asn1_db:dbget(Module,T))])
end,Objects),
io:format(F,"%%%%%%%%%%%%%%%%%%% Object Sets in ~p %%%%%%%%%%%%%%%%%%%~n",[Module]),
- lists:foreach(fun(T)-> io:format(F,"~s\n",
+ lists:foreach(fun(T)-> io:format(F,"~s.\n",
[asn1ct_pretty_format:term(asn1_db:dbget(Module,T))])
end,ObjectSets).
start() ->
diff --git a/lib/asn1/src/asn1ct_check.erl b/lib/asn1/src/asn1ct_check.erl
index fe1b2e14a8..dd77085c39 100644
--- a/lib/asn1/src/asn1ct_check.erl
+++ b/lib/asn1/src/asn1ct_check.erl
@@ -4340,11 +4340,33 @@ permitted_alphabet_merge([C1|Rest],UorI,Acc) ->
%% there will be no extension if the last constraint is without extension.
%% The rootset of all constraints are considered in the "outermoust
%% intersection". See section 13.1.2 in Dubuisson.
-constraint_merge(_S,C=[H])when is_tuple(H) ->
+constraint_merge(St, Cs0) ->
+ Cs = constraint_merge_1(St, Cs0),
+ normalize_cs(Cs).
+
+normalize_cs([{'SingleValue',[V]}|Cs]) ->
+ [{'SingleValue',V}|normalize_cs(Cs)];
+normalize_cs([{'SingleValue',[_|_]=L0}|Cs]) ->
+ [H|T] = L = lists:usort(L0),
+ [case is_range(H, T) of
+ false -> {'SingleValue',L};
+ true -> {'ValueRange',{H,lists:last(T)}}
+ end|normalize_cs(Cs)];
+normalize_cs([{'ValueRange',{Sv,Sv}}|Cs]) ->
+ [{'SingleValue',Sv}|normalize_cs(Cs)];
+normalize_cs([{'ValueRange',{'MIN','MAX'}}|Cs]) ->
+ normalize_cs(Cs);
+normalize_cs(Other) -> Other.
+
+is_range(Prev, [H|T]) when Prev =:= H - 1 -> is_range(H, T);
+is_range(_, [_|_]) -> false;
+is_range(_, []) -> true.
+
+constraint_merge_1(_S, [H]=C) when is_tuple(H) ->
C;
-constraint_merge(_S,[]) ->
+constraint_merge_1(_S, []) ->
[];
-constraint_merge(S,C) ->
+constraint_merge_1(S, C) ->
%% skip all extension but the last extension
C1 = filter_extensions(C),
%% perform all internal level intersections, intersections first
@@ -4367,17 +4389,16 @@ constraint_merge(S,C) ->
%% get the least common size constraint
SZs = get_constraints(C3,'SizeConstraint'),
CombSZ = intersection_of_size(S,SZs),
- CminusSVs=ordsets:subtract(ordsets:from_list(C3),ordsets:from_list(SVs)),
- % CminusSVsVRs = ordsets:subtract(ordsets:from_list(CminusSVs),
-% ordsets:from_list(VRs)),
- RestC = ordsets:subtract(ordsets:from_list(CminusSVs),
- ordsets:from_list(SZs)),
+ RestC = ordsets:subtract(ordsets:from_list(C3),
+ ordsets:from_list(SZs ++ VRs ++ SVs)),
%% get the least common combined constraint. That is the union of each
- %% deep costraint and merge of single value and value range constraints
- NewCs = combine_constraints(S,CombSV,CombVR,CombSZ++RestC),
- [X||X <- lists:flatten(NewCs),
- X /= intersection,
- X /= union].
+ %% deep constraint and merge of single value and value range constraints.
+ %% FIXME: Removing 'intersection' from the flattened list essentially
+ %% means that intersections are converted to unions!
+ Cs = combine_constraints(S, CombSV, CombVR, CombSZ++RestC),
+ [X || X <- lists:flatten(Cs),
+ X =/= intersection,
+ X =/= union].
%% constraint_union(S,C) takes a list of constraints as input and
%% merge them to a union. Unions are performed when two
@@ -4407,16 +4428,16 @@ constraint_union(_S,C) ->
constraint_union1(S,[A={'ValueRange',_},union,B={'ValueRange',_}|Rest],Acc) ->
AunionB = constraint_union_vr([A,B]),
- constraint_union1(S,Rest,Acc ++ AunionB);
+ constraint_union1(S, AunionB++Rest, Acc);
constraint_union1(S,[A={'SingleValue',_},union,B={'SingleValue',_}|Rest],Acc) ->
AunionB = constraint_union_sv(S,[A,B]),
constraint_union1(S,Rest,Acc ++ AunionB);
constraint_union1(S,[A={'SingleValue',_},union,B={'ValueRange',_}|Rest],Acc) ->
AunionB = union_sv_vr(S,A,B),
- constraint_union1(S,Rest,Acc ++ AunionB);
+ constraint_union1(S, AunionB++Rest, Acc);
constraint_union1(S,[A={'ValueRange',_},union,B={'SingleValue',_}|Rest],Acc) ->
AunionB = union_sv_vr(S,B,A),
- constraint_union1(S,Rest,Acc ++ AunionB);
+ constraint_union1(S, AunionB++Rest, Acc);
constraint_union1(S,[union|Rest],Acc) -> %skip when unsupported constraints
constraint_union1(S,Rest,Acc);
constraint_union1(S,[A|Rest],Acc) ->
@@ -4449,15 +4470,8 @@ constraint_union_vr(VR) ->
({_,{A1,_B1}},{_,{A2,_B2}}) when is_integer(A1),is_integer(A2),A1<A2 -> true;
({_,{A,B1}},{_,{A,B2}}) when B1=<B2->true;
(_,_)->false end,
- % sort and remove duplicates
- SortedVR = lists:sort(Fun,VR),
- RemoveDup = fun([],_) ->[];
- ([H],_) -> [H];
- ([H,H|T],F) -> F([H|T],F);
- ([H|T],F) -> [H|F(T,F)]
- end,
-
- constraint_union_vr(RemoveDup(SortedVR,RemoveDup),[]).
+ SortedVR = lists:usort(Fun,VR),
+ constraint_union_vr(SortedVR, []).
constraint_union_vr([],Acc) ->
lists:reverse(Acc);
@@ -4467,8 +4481,8 @@ constraint_union_vr([{_,{Lb,Ub2}}|Rest],[{_,{Lb,_Ub1}}|Acc]) -> %Ub2 > Ub1
constraint_union_vr(Rest,[{'ValueRange',{Lb,Ub2}}|Acc]);
constraint_union_vr([{_,{_,Ub}}|Rest],A=[{_,{_,Ub}}|_Acc]) ->
constraint_union_vr(Rest,A);
-constraint_union_vr([{_,{Lb2,Ub2}}|Rest],[{_,{Lb1,Ub1}}|Acc]) when Lb2=<Ub1,
- Ub2>Ub1->
+constraint_union_vr([{_,{Lb2,Ub2}}|Rest], [{_,{Lb1,Ub1}}|Acc])
+ when Ub1 =< Lb2, Ub1 < Ub2 ->
constraint_union_vr(Rest,[{'ValueRange',{Lb1,Ub2}}|Acc]);
constraint_union_vr([{_,{_,Ub2}}|Rest],A=[{_,{_,Ub1}}|_Acc]) when Ub2=<Ub1->
constraint_union_vr(Rest,A);
@@ -4589,9 +4603,11 @@ constraint_intersection(_S,C) ->
constraint_intersection1(S,[A,intersection,B|Rest],Acc) ->
AisecB = c_intersect(S,A,B),
- constraint_intersection1(S,Rest,AisecB++Acc);
+ constraint_intersection1(S, AisecB++Rest, Acc);
constraint_intersection1(S,[A|Rest],Acc) ->
constraint_intersection1(S,Rest,[A|Acc]);
+constraint_intersection1(_, [], [C]) ->
+ C;
constraint_intersection1(_,[],Acc) ->
lists:reverse(Acc).
diff --git a/lib/asn1/src/asn1ct_constructed_per.erl b/lib/asn1/src/asn1ct_constructed_per.erl
index b29a7b3048..27070be966 100644
--- a/lib/asn1/src/asn1ct_constructed_per.erl
+++ b/lib/asn1/src/asn1ct_constructed_per.erl
@@ -108,7 +108,10 @@ gen_encode_constructed(Erule,Typename,D) when is_record(D,type) ->
emit([
{next,val}," = case [X || X <- [",Elements,
"],X =/= asn1_NOVALUE] of",nl,
- "[] -> ",{curr,val},";",nl,
+ "[] -> setelement(",
+ {asis,ExtActualGroupPos+1},",",
+ {curr,val},",",
+ "asn1_NOVALUE);",nl,
"_ -> setelement(",{asis,ExtActualGroupPos+1},",",
{curr,val},",",
"{extaddgroup,", Elements,"})",nl,
@@ -1099,10 +1102,11 @@ gen_dec_components_call(Erule,TopType,CL={Root1,ExtList,Root2},
{EmitExts,_} = gen_dec_comp_calls(NewExtList, Erule, TopType, OptTable,
DecInfObj, Ext, NumberOfOptionals,
Tpos, []),
+ NumExtsToSkip = ext_length(ExtList),
Finish =
fun(St) ->
emit([{next,bytes},"= ?RT_PER:skipextensions(",{curr,bytes},",",
- length(ExtList)+1,",Extensions)"]),
+ NumExtsToSkip+1,",Extensions)"]),
asn1ct_name:new(bytes),
St
end,
@@ -1361,7 +1365,7 @@ gen_dec_line_open_type(_, _, _) ->
fun() -> St end}
end}.
-gen_dec_line_special(_, {typefield,_}, _TopType, Comp,
+gen_dec_line_special(Erule, {typefield,_}, _TopType, Comp,
DecInfObj, Ext) ->
#'ComponentType'{name=Cname,typespec=Type,prop=Prop} = Comp,
fun({_BytesVar,PrevSt}) ->
@@ -1370,13 +1374,14 @@ gen_dec_line_special(_, {typefield,_}, _TopType, Comp,
{Name,RestFieldNames} =
(Type#type.def)#'ObjectClassFieldType'.fieldname,
- asn1ct_name:new(tmpterm),
asn1ct_name:new(reason),
- emit([indent(2),"{",{curr,tmpterm},", ",{next,bytes},
- "} = ?RT_PER:decode_open_type(",{curr,bytes},
- ", []),",nl]),
- emit([indent(2),"case (catch ObjFun(",
- {asis,Name},",",{curr,tmpterm},",telltype,",
+ Imm = asn1ct_imm:per_dec_open_type(is_aligned(Erule)),
+ BytesVar = asn1ct_gen:mk_var(asn1ct_name:curr(bytes)),
+ {TmpTerm,TempBuf} = asn1ct_imm:dec_slim_cg(Imm, BytesVar),
+ emit([com,nl,
+ {next,bytes}," = ",TempBuf,com,nl,
+ indent(2),"case (catch ObjFun(",
+ {asis,Name},",",TmpTerm,",telltype,",
{asis,RestFieldNames},")) of", nl]),
emit([indent(4),"{'EXIT',",{curr,reason},"} ->",nl]),
emit([indent(6),"exit({'Type not ",
@@ -1402,8 +1407,10 @@ gen_dec_line_special(_, {typefield,_}, _TopType, Comp,
end,
{Name,RestFieldNames} =
(Type#type.def)#'ObjectClassFieldType'.fieldname,
- emit(["?RT_PER:decode_open_type(",{curr,bytes},
- ", []),",nl]),
+ Imm = asn1ct_imm:per_dec_open_type(is_aligned(Erule)),
+ BytesVar = asn1ct_gen:mk_var(asn1ct_name:curr(bytes)),
+ asn1ct_imm:dec_code_gen(Imm, BytesVar),
+ emit([com,nl]),
if
Ext == noext andalso Prop == mandatory ->
emit([{curr,term}," =",nl," "]);
@@ -1429,8 +1436,9 @@ gen_dec_line_special(_, {typefield,_}, _TopType, Comp,
end,
{[],PrevSt};
_ ->
- emit(["?RT_PER:decode_open_type(",{curr,bytes},
- ", [])"]),
+ Imm = asn1ct_imm:per_dec_open_type(is_aligned(Erule)),
+ BytesVar = asn1ct_gen:mk_var(asn1ct_name:curr(bytes)),
+ asn1ct_imm:dec_code_gen(Imm, BytesVar),
RefedFieldName =
(Type#type.def)#'ObjectClassFieldType'.fieldname,
@@ -1440,10 +1448,12 @@ gen_dec_line_special(_, {typefield,_}, _TopType, Comp,
Prop}],PrevSt}
end
end;
-gen_dec_line_special(_, {objectfield,PrimFieldName1,PFNList}, _TopType,
+gen_dec_line_special(Erule, {objectfield,PrimFieldName1,PFNList}, _TopType,
Comp, _DecInfObj, _Ext) ->
fun({_BytesVar,PrevSt}) ->
- emit(["?RT_PER:decode_open_type(",{curr,bytes},", [])"]),
+ Imm = asn1ct_imm:per_dec_open_type(is_aligned(Erule)),
+ BytesVar = asn1ct_gen:mk_var(asn1ct_name:curr(bytes)),
+ asn1ct_imm:dec_code_gen(Imm, BytesVar),
#'ComponentType'{name=Cname,prop=Prop} = Comp,
SaveBytes = [{Cname,{PrimFieldName1,PFNList},
asn1ct_gen:mk_var(asn1ct_name:curr(term)),
@@ -1666,20 +1676,15 @@ gen_dec_choice1(Erule,TopType,CompList,{ext,ExtPos,ExtNum}) ->
length(CompList)-ExtNum,",Ext ),",nl}),
emit({"{Cname,{Val,NewBytes}} = case Choice + Ext*",ExtPos-1," of",nl}),
gen_dec_choice2(Erule,TopType,CompList,{ext,ExtPos,ExtNum}),
- case Erule of
- per ->
- emit([";",nl,"_ -> {asn1_ExtAlt,",nl,
- " fun() -> ",nl,
- " {XTerm,XBytes} = ?RT_PER:decode_open_type(",
- {curr,bytes},",[]),",nl,
- " {binary_to_list(XTerm),XBytes}",nl,
- " end()}"]);
- _ ->
- emit([";",nl,"_ -> {asn1_ExtAlt, ?RT_PER:decode_open_type(",
- {curr,bytes},",[])}"])
- end,
- emit({nl,"end,",nl}),
- emit({nl,"{{Cname,Val},NewBytes}"}).
+ Imm = asn1ct_imm:per_dec_open_type(is_aligned(Erule)),
+ BytesVar = asn1ct_gen:mk_var(asn1ct_name:curr(bytes)),
+ emit([";",nl,
+ "_ ->",nl]),
+ {TmpTerm,TmpBuf} = asn1ct_imm:dec_slim_cg(Imm, BytesVar),
+ emit([com,nl,
+ "{asn1_ExtAlt,{",TmpTerm,com,TmpBuf,"}}",nl,
+ "end,",nl,nl,
+ "{{Cname,Val},NewBytes}"]).
gen_dec_choice2(Erule,TopType,L,Ext) ->
diff --git a/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl b/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
index 00c3dd98b2..664dfc2086 100644
--- a/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
+++ b/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
@@ -114,16 +114,6 @@ gen_encode(Erules,Typename,Type) when is_record(Type,type) ->
_ -> % embedded type with constructed name
true
end,
- case lists:member(InnerType,['SET','SEQUENCE']) of
- true ->
- true;
- _ ->
- emit([nl,"'enc_",asn1ct_gen:list2name(Typename),
- "'({'",asn1ct_gen:list2name(Typename),
- "',Val}, TagIn",ObjFun,") ->",nl]),
- emit([" 'enc_",asn1ct_gen:list2name(Typename),
- "'(Val, TagIn",ObjFun,");",nl,nl])
- end,
emit(["'enc_",asn1ct_gen:list2name(Typename),
"'(Val, TagIn",ObjFun,") ->",nl," "]),
asn1ct_gen:gen_encode_constructed(Erules,Typename,InnerType,Type);
@@ -157,15 +147,6 @@ gen_encode_user(Erules,D) when is_record(D,typedef) ->
"'(Val",") ->",nl]),
emit([" 'enc_",asn1ct_gen:list2name(Typename),
"'(Val, ", {asis,lists:reverse(Tag)},").",nl,nl]),
-
- case lists:member(InnerType,['SET','SEQUENCE']) of
- true ->
- true;
- _ ->
- emit({nl,"'enc_",asn1ct_gen:list2name(Typename),
- "'({'",asn1ct_gen:list2name(Typename),"',Val}, TagIn) ->",nl}),
- emit({" 'enc_",asn1ct_gen:list2name(Typename),"'(Val, TagIn);",nl,nl})
- end,
emit({"'enc_",asn1ct_gen:list2name(Typename),"'(Val, TagIn) ->",nl}),
CurrentMod = get(currmod),
case asn1ct_gen:type(InnerType) of
diff --git a/lib/asn1/src/asn1ct_gen_per.erl b/lib/asn1/src/asn1ct_gen_per.erl
index eb4cfdccc6..af19edb908 100644
--- a/lib/asn1/src/asn1ct_gen_per.erl
+++ b/lib/asn1/src/asn1ct_gen_per.erl
@@ -79,18 +79,6 @@ gen_encode(Erules,Typename,Type) when is_record(Type,type) ->
end,
case asn1ct_gen:type(InnerType) of
{constructed,bif} ->
- case InnerType of
- 'SET' ->
- true;
- 'SEQUENCE' ->
- true;
- _ ->
- emit({nl,"'enc_",asn1ct_gen:list2name(Typename),
- "'({'",asn1ct_gen:list2name(Typename),
- "',Val}",ObjFun,") ->",nl}),
- emit({"'enc_",asn1ct_gen:list2name(Typename),
- "'(Val",ObjFun,");",nl,nl})
- end,
emit({"'enc_",asn1ct_gen:list2name(Typename),"'(Val",ObjFun,
") ->",nl}),
asn1ct_gen:gen_encode_constructed(Erules,Typename,InnerType,Type);
@@ -943,7 +931,6 @@ gen_objset_dec(ObjSetName,_UniqueName,['EXTENSIONMARK'],_ClName,_ClFields,
_NthObj) ->
emit({"'getdec_",ObjSetName,"'(_, _) ->",nl}),
emit({indent(3),"fun(Attr1, Bytes, _,_) ->",nl}),
-%% emit({indent(6),"?RT_PER:decode_open_type(Bytes,[])",nl}),
emit({indent(6),"{Bytes,Attr1}",nl}),
emit({indent(3),"end.",nl,nl}),
ok;
@@ -959,76 +946,42 @@ emit_default_getdec(ObjSetName,UniqueName) ->
emit([indent(2), "fun(C,V,_,_) -> exit({{component,C},{value,V},{unique_name_and_value,",{asis,UniqueName},",ErrV}}) end"]).
-gen_inlined_dec_funs(Fields,[{typefield,Name,_}|Rest],
- ObjSetName,NthObj) ->
- CurrMod = get(currmod),
- InternalDefFunName = [NthObj,Name,ObjSetName],
- case lists:keysearch(Name,1,Fields) of
- {value,{_,Type}} when is_record(Type,type) ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- N=emit_inner_of_decfun(Type,InternalDefFunName),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj+N);
- {value,{_,Type}} when is_record(Type,typedef) ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- emit({indent(9),{asis,Name}," ->",nl}),
- N=emit_inner_of_decfun(Type,InternalDefFunName),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj+N);
- {value,{_,#'Externaltypereference'{module=CurrMod,type=T}}} ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- emit({indent(9),{asis,Name}," ->",nl}),
- emit([indent(12),"'dec_",T,"'(Val, telltype)"]),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj);
- {value,{_,#'Externaltypereference'{module=M,type=T}}} ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- emit({indent(9),{asis,Name}," ->",nl}),
- emit([indent(12),"'",M,"':'dec_",T,"'(Val, telltype)"]),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj);
- false ->
- emit([indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl,
- indent(9),{asis,Name}," ->{Val,Type}"]),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj)
- end;
-gen_inlined_dec_funs(Fields,[_|Rest],ObjSetName,NthObj) ->
- gen_inlined_dec_funs(Fields,Rest,ObjSetName,NthObj);
-gen_inlined_dec_funs(_,[],_,NthObj) ->
+gen_inlined_dec_funs(Fields, List, ObjSetName, NthObj0) ->
+ emit([indent(3),"fun(Type, Val, _, _) ->",nl,
+ indent(6),"case Type of",nl]),
+ NthObj = gen_inlined_dec_funs1(Fields, List, ObjSetName, "", NthObj0),
+ emit([nl,indent(6),"end",nl,
+ indent(3),"end"]),
NthObj.
-gen_inlined_dec_funs1(Fields,[{typefield,Name,_}|Rest],
- ObjSetName,NthObj) ->
+gen_inlined_dec_funs1(Fields, [{typefield,Name,_}|Rest],
+ ObjSetName, Sep0, NthObj) ->
CurrentMod = get(currmod),
InternalDefFunName = [NthObj,Name,ObjSetName],
- N=case lists:keysearch(Name,1,Fields) of
- {value,{_,Type}} when is_record(Type,type) ->
- emit({";",nl}),
- emit_inner_of_decfun(Type,InternalDefFunName);
- {value,{_,Type}} when is_record(Type,typedef) ->
- emit({";",nl,indent(9),{asis,Name}," ->",nl}),
- emit_inner_of_decfun(Type,InternalDefFunName);
- {value,{_,#'Externaltypereference'{module=CurrentMod,type=T}}} ->
- emit([";",nl,indent(9),{asis,Name}," ->",nl]),
- emit([indent(12),"'dec_",T,"'(Val,telltype)"]),
- 0;
- {value,{_,#'Externaltypereference'{module=M,type=T}}} ->
- emit([";",nl,indent(9),{asis,Name}," ->",nl]),
- emit([indent(12),"'",M,"'",":'dec_",T,"'(Val,telltype)"]),
- 0;
- false ->
- emit([";",nl,
- indent(9),{asis,Name}," ->{Val,Type}"]),
- 0
- end,
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj+N);
-gen_inlined_dec_funs1(Fields,[_|Rest],ObjSetName,NthObj)->
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj);
-gen_inlined_dec_funs1(_,[],_,NthObj) ->
- emit({nl,indent(6),"end",nl}),
- emit({indent(3),"end"}),
- NthObj.
+ emit(Sep0),
+ Sep = [";",nl],
+ N = case lists:keyfind(Name, 1, Fields) of
+ {_,#type{}=Type} ->
+ emit_inner_of_decfun(Type, InternalDefFunName);
+ {_,#typedef{}=Type} ->
+ emit([indent(9),{asis,Name}," ->",nl]),
+ emit_inner_of_decfun(Type, InternalDefFunName);
+ {_,#'Externaltypereference'{module=CurrentMod,type=T}} ->
+ emit([indent(9),{asis,Name}," ->",nl,
+ indent(12),"'dec_",T,"'(Val,telltype)"]),
+ 0;
+ {_,#'Externaltypereference'{module=M,type=T}} ->
+ emit([indent(9),{asis,Name}," ->",nl,
+ indent(12),"'",M,"':'dec_",T,"'(Val,telltype)"]),
+ 0;
+ false ->
+ emit([indent(9),{asis,Name}," -> {Val,Type}"]),
+ 0
+ end,
+ gen_inlined_dec_funs1(Fields, Rest, ObjSetName, Sep, NthObj+N);
+gen_inlined_dec_funs1(Fields, [_|Rest], ObjSetName, Sep, NthObj) ->
+ gen_inlined_dec_funs1(Fields, Rest, ObjSetName, Sep, NthObj);
+gen_inlined_dec_funs1(_, [], _, _, NthObj) -> NthObj.
emit_inner_of_decfun(#typedef{name={ExtName,Name},typespec=Type},
InternalDefFunName) ->
@@ -1147,6 +1100,10 @@ gen_dec_imm(Erule, #type{def=Name,constraint=C}) ->
end,
gen_dec_imm_1(Name, C, Aligned).
+gen_dec_imm_1('ASN1_OPEN_TYPE', Constraint, Aligned) ->
+ imm_decode_open_type(Constraint, Aligned);
+gen_dec_imm_1('ANY', _Constraint, Aligned) ->
+ imm_decode_open_type([], Aligned);
gen_dec_imm_1('BOOLEAN', _Constr, _Aligned) ->
asn1ct_imm:per_dec_boolean();
gen_dec_imm_1({'ENUMERATED',{Base,Ext}}, _Constr, Aligned) ->
@@ -1239,36 +1196,6 @@ gen_dec_prim_1(Erule,
",",{asis,Constraint},")"});
'UTF8String' ->
emit({"?RT_PER:decode_UTF8String(",BytesVar,")"});
- 'ANY' ->
- case Erule of
- per ->
- emit(["fun() -> {XTerm,YTermXBytes} = ?RT_PER:decode_open_type(",BytesVar,",",{asis,Constraint}, "), {binary_to_list(XTerm),XBytes} end ()"]);
- _ ->
- emit(["?RT_PER:decode_open_type(",BytesVar,",",
- {asis,Constraint}, ")"])
- end;
- 'ASN1_OPEN_TYPE' ->
- case Constraint of
- [#'Externaltypereference'{type=Tname}] ->
- emit(["fun(FBytes) ->",nl,
- " {XTerm,XBytes} = "]),
- emit(["?RT_PER:decode_open_type(FBytes,[]),",nl]),
- emit([" {YTerm,_} = dec_",Tname,"(XTerm,mandatory),",nl]),
- emit([" {YTerm,XBytes} end(",BytesVar,")"]);
- [#type{def=#'Externaltypereference'{type=Tname}}] ->
- emit(["fun(FBytes) ->",nl,
- " {XTerm,XBytes} = "]),
- emit(["?RT_PER:decode_open_type(FBytes,[]),",nl]),
- emit([" {YTerm,_} = dec_",Tname,"(XTerm,mandatory),",nl]),
- emit([" {YTerm,XBytes} end(",BytesVar,")"]);
- _ ->
- case Erule of
- per ->
- emit(["fun() -> {XTerm,XBytes} = ?RT_PER:decode_open_type(",BytesVar,", []), {binary_to_list(XTerm),XBytes} end()"]);
- _ ->
- emit(["?RT_PER:decode_open_type(",BytesVar,",[])"])
- end
- end;
#'ObjectClassFieldType'{} ->
case asn1ct_gen:get_inner(Typename) of
{fixedtypevaluefield,_,InnerType} ->
@@ -1334,3 +1261,22 @@ extaddgroup2sequence([C|T],ExtNum,Acc) ->
extaddgroup2sequence(T,ExtNum,[C|Acc]);
extaddgroup2sequence([],_,Acc) ->
lists:reverse(Acc).
+
+imm_decode_open_type([#'Externaltypereference'{type=Tname}], Aligned) ->
+ imm_dec_open_type_1(Tname, Aligned);
+imm_decode_open_type([#type{def=#'Externaltypereference'{type=Tname}}],
+ Aligned) ->
+ imm_dec_open_type_1(Tname, Aligned);
+imm_decode_open_type(_, Aligned) ->
+ asn1ct_imm:per_dec_open_type(Aligned).
+
+imm_dec_open_type_1(Type, Aligned) ->
+ D = fun(OpenType, Buf) ->
+ asn1ct_name:new(tmpval),
+ emit(["begin",nl,
+ "{",{curr,tmpval},",_} = ",
+ "dec_",Type,"(",OpenType,", mandatory),",nl,
+ "{",{curr,tmpval},com,Buf,"}",nl,
+ "end"])
+ end,
+ {call,D,asn1ct_imm:per_dec_open_type(Aligned)}.
diff --git a/lib/asn1/src/asn1ct_gen_per_rt2ct.erl b/lib/asn1/src/asn1ct_gen_per_rt2ct.erl
index ecd212c3e3..4f4563833f 100644
--- a/lib/asn1/src/asn1ct_gen_per_rt2ct.erl
+++ b/lib/asn1/src/asn1ct_gen_per_rt2ct.erl
@@ -69,18 +69,6 @@ gen_encode(Erules,Typename,Type) when is_record(Type,type) ->
end,
case asn1ct_gen:type(InnerType) of
{constructed,bif} ->
- case InnerType of
- 'SET' ->
- true;
- 'SEQUENCE' ->
- true;
- _ ->
- emit({nl,"'enc_",asn1ct_gen:list2name(Typename),
- "'({'",asn1ct_gen:list2name(Typename),
- "',Val}",ObjFun,") ->",nl}),
- emit({"'enc_",asn1ct_gen:list2name(Typename),
- "'(Val",ObjFun,");",nl,nl})
- end,
emit({"'enc_",asn1ct_gen:list2name(Typename),"'(Val",ObjFun,
") ->",nl}),
asn1ct_gen:gen_encode_constructed(Erules,Typename,InnerType,Type);
@@ -417,35 +405,46 @@ emit_enc_octet_string(_Erules,Constraint,Value) ->
asn1ct_name:new(tmpval),
emit({" begin",nl}),
emit({" [",{curr,tmpval},"] = ",Value,",",nl}),
- emit({" [10,8,",{curr,tmpval},"]",nl}),
+ emit([" [[10,8],",{curr,tmpval},"]",nl]),
emit(" end");
2 ->
asn1ct_name:new(tmpval),
- emit({" begin",nl}),
- emit({" [",{curr,tmpval},",",{next,tmpval},"] = ",
- Value,",",nl}),
- emit({" [[10,8,",{curr,tmpval},"],[10,8,",
- {next,tmpval},"]]",nl}),
- emit(" end"),
- asn1ct_name:new(tmpval);
- Sv when is_integer(Sv),Sv =< 256 ->
+ emit([" begin",nl,
+ " ",{curr,tmpval}," = ",Value,",",nl,
+ " case length(",{curr,tmpval},") of",nl,
+ " 2 ->",nl,
+ " [[45,16,2]|",{curr,tmpval},"];",nl,
+ " _ ->",nl,
+ " exit({error,{value_out_of_bounds,",
+ {curr,tmpval},"}})",nl,
+ " end",nl,
+ " end"]);
+ Sv when is_integer(Sv), Sv < 256 ->
asn1ct_name:new(tmpval),
- emit({" begin",nl}),
- emit({" case length(",Value,") of",nl}),
- emit([" ",{curr,tmpval}," when ",{curr,tmpval}," == ",Sv," ->"]),
- emit([" [2,20,",{curr,tmpval},",",Value,"];",nl]),
- emit({" _ -> exit({error,{value_out_of_bounds,",
- Value,"}})", nl," end",nl}),
- emit(" end");
+ asn1ct_name:new(tmplen),
+ emit([" begin",nl,
+ " ",{curr,tmpval}," = ",Value,",",nl,
+ " case length(",{curr,tmpval},") of",nl,
+ " ",Sv,"=",{curr,tmplen}," ->",nl,
+ " [20,",{curr,tmplen},"|",{curr,tmpval},"];",nl,
+ " _ ->",nl,
+ " exit({error,{value_out_of_bounds,",
+ {curr,tmpval},"}})",nl,
+ " end",nl,
+ " end"]);
Sv when is_integer(Sv),Sv =< 65535 ->
asn1ct_name:new(tmpval),
- emit({" begin",nl}),
- emit({" case length(",Value,") of",nl}),
- emit([" ",{curr,tmpval}," when ",{curr,tmpval}," == ",Sv," ->"]),
- emit([" [2,21,",{curr,tmpval},",",Value,"];",nl]),
- emit({" _ -> exit({error,{value_out_of_bounds,",
- Value,"}})",nl," end",nl}),
- emit(" end");
+ asn1ct_name:new(tmplen),
+ emit([" begin",nl,
+ " ",{curr,tmpval}," = ",Value,",",nl,
+ " case length(",{curr,tmpval},") of",nl,
+ " ",Sv,"=",{curr,tmplen}," ->",nl,
+ " [<<21,",{curr,tmplen},":16>>|",Value,"];",nl,
+ " _ ->",nl,
+ " exit({error,{value_out_of_bounds,",
+ {curr,tmpval},"}})",nl,
+ " end",nl,
+ " end"]);
C ->
emit({" ?RT_PER:encode_octet_string(",{asis,C},",false,",Value,")",nl})
end.
@@ -1292,7 +1291,6 @@ gen_objset_dec(ObjSetName,_,['EXTENSIONMARK'],_ClName,_ClFields,
_NthObj) ->
emit({"'getdec_",ObjSetName,"'(_, _) ->",nl}),
emit({indent(3),"fun(Attr1, Bytes, _, _) ->",nl}),
- %% emit({indent(6),"?RT_PER:decode_open_type(Bytes,[])",nl}),
emit({indent(6),"{Bytes,Attr1}",nl}),
emit({indent(3),"end.",nl,nl}),
ok;
@@ -1308,77 +1306,42 @@ emit_default_getdec(ObjSetName,UniqueName) ->
emit([indent(2), "fun(C,V,_,_) -> exit({{component,C},{value,V},{unique_name_and_value,",{asis,UniqueName},",ErrV}}) end"]).
-gen_inlined_dec_funs(Fields,[{typefield,Name,_}|Rest],
- ObjSetName,NthObj) ->
- CurrMod = get(currmod),
- InternalDefFunName = [NthObj,Name,ObjSetName],
- case lists:keysearch(Name,1,Fields) of
- {value,{_,Type}} when is_record(Type,type) ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- N=emit_inner_of_decfun(Type,InternalDefFunName),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj+N);
- {value,{_,Type}} when is_record(Type,typedef) ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- emit({indent(9),{asis,Name}," ->",nl}),
- N=emit_inner_of_decfun(Type,InternalDefFunName),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj+N);
- {value,{_,#'Externaltypereference'{module=CurrMod,type=T}}} ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- emit({indent(9),{asis,Name}," ->",nl}),
- emit([indent(12),"'dec_",T,"'(Val, telltype)"]),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj);
- {value,{_,#'Externaltypereference'{module=M,type=T}}} ->
- emit({indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl}),
- emit({indent(9),{asis,Name}," ->",nl}),
- emit([indent(12),"'",M,"':'dec_",T,"'(Val, telltype)"]),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj);
- false ->
- emit([indent(3),"fun(Type, Val, _, _) ->",nl,
- indent(6),"case Type of",nl,
- indent(9),{asis,Name}," -> {Val,Type}"]),
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj)
- end;
-gen_inlined_dec_funs(Fields,[_|Rest],ObjSetName,NthObj) ->
- gen_inlined_dec_funs(Fields,Rest,ObjSetName,NthObj);
-gen_inlined_dec_funs(_,[],_,NthObj) ->
+gen_inlined_dec_funs(Fields, List, ObjSetName, NthObj0) ->
+ emit([indent(3),"fun(Type, Val, _, _) ->",nl,
+ indent(6),"case Type of",nl]),
+ NthObj = gen_inlined_dec_funs1(Fields, List, ObjSetName, "", NthObj0),
+ emit([nl,indent(6),"end",nl,
+ indent(3),"end"]),
NthObj.
-gen_inlined_dec_funs1(Fields,[{typefield,Name,_}|Rest],
- ObjSetName,NthObj) ->
+gen_inlined_dec_funs1(Fields, [{typefield,Name,_}|Rest],
+ ObjSetName, Sep0, NthObj) ->
CurrentMod = get(currmod),
InternalDefFunName = [NthObj,Name,ObjSetName],
- N=
- case lists:keysearch(Name,1,Fields) of
- {value,{_,Type}} when is_record(Type,type) ->
- emit({";",nl}),
- emit_inner_of_decfun(Type,InternalDefFunName);
- {value,{_,Type}} when is_record(Type,typedef) ->
- emit({";",nl,indent(9),{asis,Name}," ->",nl}),
- emit_inner_of_decfun(Type,InternalDefFunName);
- {value,{_,#'Externaltypereference'{module=CurrentMod,type=T}}} ->
- emit([";",nl,indent(9),{asis,Name}," ->",nl]),
- emit([indent(12),"'dec_",T,"'(Val,telltype)"]),
- 0;
- {value,{_,#'Externaltypereference'{module=M,type=T}}} ->
- emit([";",nl,indent(9),{asis,Name}," ->",nl]),
- emit([indent(12),"'",M,"':'dec_",T,"'(Val,telltype)"]),
- 0;
- false ->
- emit([";",nl,
- indent(9),{asis,Name}," -> {Val,Type}"]),
- 0
- end,
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj+N);
-gen_inlined_dec_funs1(Fields,[_|Rest],ObjSetName,NthObj)->
- gen_inlined_dec_funs1(Fields,Rest,ObjSetName,NthObj);
-gen_inlined_dec_funs1(_,[],_,NthObj) ->
- emit({nl,indent(6),"end",nl}),
- emit({indent(3),"end"}),
- NthObj.
+ emit(Sep0),
+ Sep = [";",nl],
+ N = case lists:keyfind(Name, 1, Fields) of
+ {_,#type{}=Type} ->
+ emit_inner_of_decfun(Type, InternalDefFunName);
+ {_,#typedef{}=Type} ->
+ emit([indent(9),{asis,Name}," ->",nl]),
+ emit_inner_of_decfun(Type, InternalDefFunName);
+ {_,#'Externaltypereference'{module=CurrentMod,type=T}} ->
+ emit([indent(9),{asis,Name}," ->",nl,
+ indent(12),"'dec_",T,"'(Val,telltype)"]),
+ 0;
+ {_,#'Externaltypereference'{module=M,type=T}} ->
+ emit([indent(9),{asis,Name}," ->",nl,
+ indent(12),"'",M,"':'dec_",T,"'(Val,telltype)"]),
+ 0;
+ false ->
+ emit([indent(9),{asis,Name}," -> {Val,Type}"]),
+ 0
+ end,
+ gen_inlined_dec_funs1(Fields, Rest, ObjSetName, Sep, NthObj+N);
+gen_inlined_dec_funs1(Fields, [_|Rest], ObjSetName, Sep, NthObj) ->
+ gen_inlined_dec_funs1(Fields, Rest, ObjSetName, Sep, NthObj);
+gen_inlined_dec_funs1(_, [], _, _, NthObj) -> NthObj.
emit_inner_of_decfun(#typedef{name={ExtName,Name},typespec=Type},
InternalDefFunName) ->
@@ -1579,25 +1542,9 @@ gen_dec_prim(Erules,Att,BytesVar) ->
'UTF8String' ->
emit({"?RT_PER:decode_UTF8String(",BytesVar,")"});
'ANY' ->
- emit(["?RT_PER:decode_open_type(",BytesVar,",",
- {asis,Constraint}, ")"]);
+ asn1ct_gen_per:gen_dec_prim(Erules, Att, BytesVar);
'ASN1_OPEN_TYPE' ->
- case Constraint of
- [#'Externaltypereference'{type=Tname}] ->
- emit(["fun(FBytes) ->",nl,
- " {XTerm,XBytes} = "]),
- emit(["?RT_PER:decode_open_type(FBytes,[]),",nl]),
- emit([" {YTerm,_} = dec_",Tname,"(XTerm,mandatory),",nl]),
- emit([" {YTerm,XBytes} end(",BytesVar,")"]);
- [#type{def=#'Externaltypereference'{type=Tname}}] ->
- emit(["fun(FBytes) ->",nl,
- " {XTerm,XBytes} = "]),
- emit(["?RT_PER:decode_open_type(FBytes,[]),",nl]),
- emit([" {YTerm,_} = dec_",Tname,"(XTerm,mandatory),",nl]),
- emit([" {YTerm,XBytes} end(",BytesVar,")"]);
- _ ->
- emit(["?RT_PER:decode_open_type(",BytesVar,",[])"])
- end;
+ asn1ct_gen_per:gen_dec_prim(Erules, Att, BytesVar);
#'ObjectClassFieldType'{} ->
case asn1ct_gen:get_inner(Att#type.def) of
{fixedtypevaluefield,_,InnerType} ->
diff --git a/lib/asn1/src/asn1ct_parser2.erl b/lib/asn1/src/asn1ct_parser2.erl
index 7301f49085..9e1fcce2b1 100644
--- a/lib/asn1/src/asn1ct_parser2.erl
+++ b/lib/asn1/src/asn1ct_parser2.erl
@@ -924,19 +924,8 @@ parse_UnionsRec([{'|',_}|Rest]) ->
{V1,V2} ->
{[V1,union,V2],Rest3}
end;
-parse_UnionsRec([{'UNION',_}|Rest]) ->
- {InterSec,Rest2} = parse_Intersections(Rest),
- {URec,Rest3} = parse_UnionsRec(Rest2),
- case {InterSec,URec} of
- {V1,[]} ->
- {V1,Rest3};
- {{'SingleValue',V1},{'SingleValue',V2}} ->
- {{'SingleValue',ordsets:union(to_set(V1),to_set(V2))},Rest3};
- {V1,V2} when is_list(V2) ->
- {[V1] ++ [union|V2],Rest3};
- {V1,V2} ->
- {[V1,union,V2],Rest3}
- end;
+parse_UnionsRec([{'UNION',Info}|Rest]) ->
+ parse_UnionsRec([{'|',Info}|Rest]);
parse_UnionsRec(Tokens) ->
{[],Tokens}.
@@ -971,20 +960,8 @@ parse_IElemsRec([{'^',_}|Rest]) ->
{V1,V2} ->
{[V1,intersection,V2],Rest3}
end;
-parse_IElemsRec([{'INTERSECTION',_}|Rest]) ->
- {InterSec,Rest2} = parse_IntersectionElements(Rest),
- {IRec,Rest3} = parse_IElemsRec(Rest2),
- case {InterSec,IRec} of
- {{'SingleValue',V1},{'SingleValue',V2}} ->
- {{'SingleValue',
- ordsets:intersection(to_set(V1),to_set(V2))},Rest3};
- {V1,[]} ->
- {V1,Rest3};
- {V1,V2} when is_list(V2) ->
- {[V1] ++ [intersection|V2],Rest3};
- {V1,V2} ->
- {[V1,intersection,V2],Rest3}
- end;
+parse_IElemsRec([{'INTERSECTION',Info}|Rest]) ->
+ parse_IElemsRec([{'^',Info}|Rest]);
parse_IElemsRec(Tokens) ->
{[],Tokens}.
diff --git a/lib/asn1/src/asn1rt_uper_bin.erl b/lib/asn1/src/asn1rt_uper_bin.erl
index 9410c3ef90..fc65d80245 100644
--- a/lib/asn1/src/asn1rt_uper_bin.erl
+++ b/lib/asn1/src/asn1rt_uper_bin.erl
@@ -120,14 +120,15 @@ fixextensions(Pos,ExtPos,Val,Acc) ->
end,
fixextensions(Pos+1,ExtPos,Val,(Acc bsl 1)+Bit).
-skipextensions(Bytes,Nr,ExtensionBitPattern) ->
- case (catch element(Nr,ExtensionBitPattern)) of
- 1 ->
+skipextensions(Bytes,Nr,ExtensionBitstr) when is_bitstring(ExtensionBitstr) ->
+ Prev = Nr - 1,
+ case ExtensionBitstr of
+ <<_:Prev,1:1,_/bitstring>> ->
{_,Bytes2} = decode_open_type(Bytes,[]),
- skipextensions(Bytes2, Nr+1, ExtensionBitPattern);
- 0 ->
- skipextensions(Bytes, Nr+1, ExtensionBitPattern);
- {'EXIT',_} -> % badarg, no more extensions
+ skipextensions(Bytes2, Nr+1, ExtensionBitstr);
+ <<_:Prev,0:1,_/bitstring>> ->
+ skipextensions(Bytes, Nr+1, ExtensionBitstr);
+ _ ->
Bytes
end.