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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
655
655
    CRange = greatest_common_range(SV,VR),
656
656
    pre_encode(integer,CRange);
657
657
effective_constraint(bitstring,C) ->
658
 
%     Constr=get_constraints(C,'SizeConstraint'),
659
 
%     case Constr of
660
 
%       [] -> no;
661
 
%       [{'SizeConstraint',Val}] -> Val;
662
 
%       Other -> Other
663
 
%     end;
664
 
    get_constraint(C,'SizeConstraint');
665
 
effective_constraint(Type,C) ->
666
 
    io:format("Effective constraint for ~p, not implemented yet.~n",[Type]),
667
 
    C.
 
658
    get_constraint(C,'SizeConstraint').
668
659
 
669
660
effective_constr(_,[]) ->
670
661
    [];
671
662
effective_constr('SingleValue',List) ->
672
663
    SVList = lists:flatten(lists:map(fun(X)->element(2,X)end,List)),
673
664
    % sort and remove duplicates
674
 
%    SortedSVList = lists:sort(SVList),
675
665
    RemoveDup = fun([],_) ->[];
676
666
                   ([H],_) -> [H];
677
667
                   ([H,H|T],F) -> F([H|T],F);
720
710
        _ -> lists:max(L)
721
711
    end.
722
712
 
723
 
% effective_constraint1('SingleValue',List) ->
724
 
%     SVList = lists:map(fun(X)->element(2,X)end,List),
725
 
%     sv_effective_constraint(hd(SVList),tl(SVList));
726
 
% effective_constraint1('ValueRange',List) ->
727
 
%     VRList = lists:map(fun(X)->element(2,X)end,List),
728
 
%     vr_effective_constraint(lists:map(fun(X)->element(1,X)end,VRList),
729
 
%                           lists:map(fun(X)->element(2,X)end,VRList)).
730
 
 
731
 
%% vr_effective_constraint/2
732
 
%% Gets all LowerEndPoints and UpperEndPoints as arguments
733
 
%% Returns {'ValueRange',{Lb,Ub}} where Lb is the highest value of
734
 
%% the LowerEndPoints and Ub is the lowest value of the UpperEndPoints,
735
 
%% i.e. the intersection of all value ranges.
736
 
% vr_effective_constraint(Mins,Maxs) ->
737
 
%     Lb=lists:foldl(fun(X,'MIN') when integer(X) -> X;
738
 
%                     (X,'MIN') -> 'MIN';
739
 
%                     (X,AccIn) when integer(X),X >= AccIn -> X;
740
 
%                     (X,AccIn) -> AccIn
741
 
%                  end,hd(Mins),tl(Mins)),
742
 
%     Ub = lists:min(Maxs),
743
 
%     {'ValueRange',{Lb,Ub}}.
744
 
                           
745
 
 
746
 
% sv_effective_constraint(SV,[]) ->
747
 
%     {'SingleValue',SV};
748
 
% sv_effective_constraint([],_) ->
749
 
%     exit({error,{asn1,{illegal_single_value_constraint}}});
750
 
% sv_effective_constraint(SV,[SV|Rest]) ->
751
 
%     sv_effective_constraint(SV,Rest);
752
 
% sv_effective_constraint(Int,[SV|Rest]) when integer(Int),list(SV) ->
753
 
%     case lists:member(Int,SV) of
754
 
%       true ->
755
 
%           sv_effective_constraint(Int,Rest);
756
 
%       _ ->
757
 
%           exit({error,{asn1,{illegal_single_value_constraint}}})
758
 
%     end;
759
 
% sv_effective_constraint(SV,[Int|Rest]) when integer(Int),list(SV) ->
760
 
%     case lists:member(Int,SV) of
761
 
%       true ->
762
 
%           sv_effective_constraint(Int,Rest);
763
 
%       _ ->
764
 
%           exit({error,{asn1,{illegal_single_value_constraint}}})
765
 
%     end;
766
 
% sv_effective_constraint(SV1,[SV2|Rest]) when list(SV1),list(SV2) ->
767
 
%     sv_effective_constraint(common_set(SV1,SV2),Rest);
768
 
% sv_effective_constraint(_,_) ->
769
 
%     exit({error,{asn1,{illegal_single_value_constraint}}}).
770
 
 
771
 
%% common_set/2
772
 
%% Two lists as input
773
 
%% Returns the list with all elements that are common for both
774
 
%% input lists
775
 
% common_set(SV1,SV2) ->
776
 
%     lists:filter(fun(X)->lists:member(X,SV1) end,SV2).
777
713
 
778
714
 
779
715
 
827
763
    gen_encode_constr_type(Erules,EncConstructed),
828
764
    emit(nl),
829
765
    DecConstructed =
830
 
%       gen_decode_objectfields(Class#classdef.typespec,ObjName,Fields,[]),
831
766
        gen_decode_objectfields(ClassName,get_class_fields(Class),
832
767
                                ObjName,Fields,[]),
833
768
    emit(nl),
926
861
gen_encode_objectfields(_,[],_,_,Acc) ->
927
862
    Acc.
928
863
 
929
 
% gen_encode_objectfields(Class,ObjName,[{FieldName,Type}|Rest],ConstrAcc) ->
930
 
%     Fields = Class#objectclass.fields,
931
 
 
932
 
%     MaybeConstr =
933
 
%     case is_typefield(Fields,FieldName) of
934
 
%       true ->
935
 
%           Def = Type#typedef.typespec,
936
 
%           emit({"'enc_",ObjName,"'(",{asis,FieldName},
937
 
%                 ", Val, Dummy) ->",nl}),
938
 
 
939
 
%           CAcc =
940
 
%           case Type#typedef.name of
941
 
%               {primitive,bif} ->
942
 
%                   gen_encode_prim(per,Def,"false","Val"),
943
 
%                   [];
944
 
%               {constructed,bif} ->
945
 
%                   emit({"   'enc_",ObjName,'_',FieldName,
946
 
%                         "'(Val)"}),
947
 
%                       [{['enc_',ObjName,'_',FieldName],Def}];
948
 
%               {ExtMod,TypeName} ->
949
 
%                   emit({"   '",ExtMod,"':'enc_",TypeName,"'(Val)"}),
950
 
%                   [];
951
 
%               TypeName ->
952
 
%                   emit({"   'enc_",TypeName,"'(Val)"}),
953
 
%                   []
954
 
%           end,
955
 
%           case more_genfields(Fields,Rest) of
956
 
%               true ->
957
 
%                   emit({";",nl});
958
 
%               false ->
959
 
%                   emit({".",nl})
960
 
%           end,
961
 
%           CAcc;
962
 
%       {false,objectfield} ->
963
 
%           emit({"'enc_",ObjName,"'(",{asis,FieldName},
964
 
%                 ", Val, [H|T]) ->",nl}),
965
 
%           case Type#typedef.name of
966
 
%               {ExtMod,TypeName} ->
967
 
%                   emit({indent(3),"'",ExtMod,"':'enc_",TypeName,
968
 
%                         "'(H, Val, T)"});
969
 
%               TypeName ->
970
 
%                   emit({indent(3),"'enc_",TypeName,"'(H, Val, T)"})
971
 
%           end,
972
 
%           case more_genfields(Fields,Rest) of
973
 
%               true ->
974
 
%                   emit({";",nl});
975
 
%               false ->
976
 
%                   emit({".",nl})
977
 
%           end,
978
 
%           [];
979
 
%       {false,_} -> []
980
 
%     end,
981
 
%     gen_encode_objectfields(Class,ObjName,Rest,MaybeConstr ++ ConstrAcc);
982
 
% gen_encode_objectfields(C,O,[_|T],Acc) ->
983
 
%     gen_encode_objectfields(C,O,T,Acc);
984
 
% gen_encode_objectfields(_,_,[],Acc) ->
985
 
%     Acc.
 
864
 
986
865
 
987
866
gen_encode_constr_type(Erules,[TypeDef|Rest]) when record(TypeDef,typedef) ->
988
867
    case is_already_generated(enc,TypeDef#typedef.name) of
1187
1066
 
1188
1067
%%%%%%%%%%%%%%%
1189
1068
 
1190
 
% gen_decode_objectfields(Class,ObjName,[{FieldName,Type}|Rest],ConstrAcc) ->
1191
 
%     Fields = Class#objectclass.fields,
1192
 
 
1193
 
%     MaybeConstr =
1194
 
%     case is_typefield(Fields,FieldName) of
1195
 
%       true ->
1196
 
%           Def = Type#typedef.typespec,
1197
 
%           emit({"'dec_",ObjName,"'(",{asis,FieldName},
1198
 
%                 ", Val, Telltype, RestPrimFieldName) ->",nl}),
1199
 
 
1200
 
%           CAcc =
1201
 
%           case Type#typedef.name of
1202
 
%               {primitive,bif} ->
1203
 
%                   gen_dec_prim(per,Def,"Val"),
1204
 
%                   [];
1205
 
%               {constructed,bif} ->
1206
 
%                   emit({"   'dec_",ObjName,'_',FieldName,
1207
 
%                         "'(Val, Telltype)"}),
1208
 
%                   [{['dec_',ObjName,'_',FieldName],Def}];
1209
 
%               {ExtMod,TypeName} ->
1210
 
%                   emit({"   '",ExtMod,"':'dec_",TypeName,
1211
 
%                         "'(Val, Telltype)"}),
1212
 
%                   [];
1213
 
%               TypeName ->
1214
 
%                   emit({"   'dec_",TypeName,"'(Val, Telltype)"}),
1215
 
%                   []
1216
 
%           end,
1217
 
%           case more_genfields(Fields,Rest) of
1218
 
%               true ->
1219
 
%                   emit({";",nl});
1220
 
%               false ->
1221
 
%                   emit({".",nl})
1222
 
%           end,
1223
 
%           CAcc;
1224
 
%       {false,objectfield} ->
1225
 
%           emit({"'dec_",ObjName,"'(",{asis,FieldName},
1226
 
%                 ", Val, Telltype, [H|T]) ->",nl}),
1227
 
%           case Type#typedef.name of
1228
 
%               {ExtMod,TypeName} ->
1229
 
%                   emit({indent(3),"'",ExtMod,"':'dec_",TypeName,
1230
 
%                         "'(H, Val, Telltype, T)"});
1231
 
%               TypeName ->
1232
 
%                   emit({indent(3),"'dec_",TypeName,
1233
 
%                         "'(H, Val, Telltype, T)"})
1234
 
%           end,
1235
 
%           case more_genfields(Fields,Rest) of
1236
 
%               true ->
1237
 
%                   emit({";",nl});
1238
 
%               false ->
1239
 
%                   emit({".",nl})
1240
 
%           end,
1241
 
%           [];
1242
 
%       {false,_} ->
1243
 
%           []
1244
 
%     end,
1245
 
%     gen_decode_objectfields(Class,ObjName,Rest,MaybeConstr ++ ConstrAcc);
1246
 
% gen_decode_objectfields(C,O,[_|T],CAcc) ->
1247
 
%     gen_decode_objectfields(C,O,T,CAcc);
1248
 
% gen_decode_objectfields(_,_,[],CAcc) ->
1249
 
%     CAcc.
1250
 
 
1251
 
gen_decode_constr_type(Erules,[{Name,Def}|Rest]) ->
1252
 
    emit({Name,"(Bytes,_) ->",nl}),
1253
 
    InnerType = asn1ct_gen:get_inner(Def#type.def),
1254
 
    asn1ct_gen:gen_decode_constructed(Erules,Name,InnerType,Def),
1255
 
    gen_decode_constr_type(Erules,Rest);
 
1069
 
1256
1070
gen_decode_constr_type(Erules,[TypeDef|Rest]) when record(TypeDef,typedef) ->
1257
1071
    case is_already_generated(dec,TypeDef#typedef.name) of
1258
1072
        true -> ok;
1263
1077
gen_decode_constr_type(_,[]) ->
1264
1078
    ok.
1265
1079
 
1266
 
% is_typefield(Fields,FieldName) ->
1267
 
%     case lists:keysearch(FieldName,2,Fields) of
1268
 
%       {value,Field} ->
1269
 
%           case element(1,Field) of
1270
 
%               typefield ->
1271
 
%                   true;
1272
 
%               Other ->
1273
 
%                   {false,Other}
1274
 
%           end;
1275
 
%       _ ->
1276
 
%           false
1277
 
%     end.
1278
1080
%% Object Set code generating for encoding and decoding
1279
1081
%% ----------------------------------------------------
1280
1082
gen_objectset_code(Erules,ObjSet) ->
1957
1759
        _ -> ok
1958
1760
    end.
1959
1761
 
1960
 
% dec_enumerated_cases(NNL,Tmpremain,No) ->
1961
 
%     Cases=dec_enumerated_cases1(NNL,Tmpremain,0),
1962
 
%     lists:flatten(io_lib:format("(case ~s "++Cases++
1963
 
%                 "~s when atom(~s)->exit({error,{asn1,{namednumber,~s}}});_->~s end)",[Value,"TmpVal","TmpVal","TmpVal",Value])).
1964
1762
 
1965
1763
dec_enumerated_cases([Name|Rest],Tmpremain,No) ->
1966
1764
    io_lib:format("~w->{~w,~s};",[No,Name,Tmpremain])++
1967
1765
        dec_enumerated_cases(Rest,Tmpremain,No+1);
1968
1766
dec_enumerated_cases([],_,_) ->
1969
1767
    "".
1970
 
 
1971
 
 
1972
 
% more_genfields(_Fields,[]) ->
1973
 
%     false;
1974
 
% more_genfields(Fields,[{FieldName,_}|T]) ->
1975
 
%     case is_typefield(Fields,FieldName) of
1976
 
%       true -> true;
1977
 
%       {false,objectfield} -> true;
1978
 
%       {false,_} -> more_genfields(Fields,T)
1979
 
%     end.