~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
142
142
    case D#type.def of
143
143
        'INTEGER' ->
144
144
            emit({"?RT_PER:encode_integer(", %fel
145
 
                  {asis,Constraint},",",Value,")"});
 
145
                  {asis,effective_constraint(integer,Constraint)},",",Value,")"});
146
146
        {'INTEGER',NamedNumberList} ->
147
147
            emit({"?RT_PER:encode_integer(",
148
 
                  {asis,Constraint},",",Value,",",
 
148
                  {asis,effective_constraint(integer,Constraint)},",",Value,",",
149
149
                  {asis,NamedNumberList},")"});
150
150
        {'ENUMERATED',{Nlist1,Nlist2}} ->
151
151
            NewList = lists:concat([[{0,X}||{X,_} <- Nlist1],['EXT_MARK'],[{1,X}||{X,_} <- Nlist2]]),
257
257
emit_enc_enumerated_case(C, EnumName, Count) ->
258
258
    emit(["'",EnumName,"' -> ?RT_PER:encode_integer(",{asis,C},", ",Count,")"]).
259
259
 
 
260
%% effective_constraint(Type,C)
 
261
%% Type = atom()
 
262
%% C = [C1,...]
 
263
%% C1 = {'SingleValue',SV} | {'ValueRange',VR} | {atom(),term()}
 
264
%% SV = integer() | [integer(),...]
 
265
%% VR = {Lb,Ub}
 
266
%% Lb = 'MIN' | integer()
 
267
%% Ub = 'MAX' | integer()
 
268
%% Returns a single value if C only has a single value constraint, and no
 
269
%% value range constraints, that constrains to a single value, otherwise 
 
270
%% returns a value range that has the lower bound set to the lowest value 
 
271
%% of all single values and lower bound values in C and the upper bound to
 
272
%% the greatest value.
 
273
effective_constraint(integer,[C={{_,_},_}|_Rest]) -> % extension
 
274
    [C]; %% [C|effective_constraint(integer,Rest)]; XXX what is possible ???
 
275
effective_constraint(integer,C) ->
 
276
    SVs = get_constraints(C,'SingleValue'),
 
277
    SV = effective_constr('SingleValue',SVs),
 
278
    VRs = get_constraints(C,'ValueRange'),
 
279
    VR = effective_constr('ValueRange',VRs),
 
280
    greatest_common_range(SV,VR);
 
281
% effective_constraint(bitstring,C) ->
 
282
%     Constr=get_constraints(C,'SizeConstraint'),
 
283
%     case Constr of
 
284
%       [] -> no;
 
285
%       [{'SizeConstraint',Val}] -> Val;
 
286
%       Other -> Other
 
287
%     end;
 
288
%     get_constraint(C,'SizeConstraint');
 
289
effective_constraint(Type,C) ->
 
290
    io:format("Effective constraint for ~p, not implemented yet.~n",[Type]),
 
291
    C.
 
292
 
 
293
effective_constr(_,[]) ->
 
294
    [];
 
295
effective_constr('SingleValue',List) ->
 
296
    SVList = lists:flatten(lists:map(fun(X)->element(2,X)end,List)),
 
297
    % sort and remove duplicates
 
298
%    SortedSVList = lists:sort(SVList),
 
299
    RemoveDup = fun([],_) ->[];
 
300
                   ([H],_) -> [H];
 
301
                   ([H,H|T],F) -> F([H|T],F);
 
302
                   ([H|T],F) -> [H|F(T,F)]
 
303
                end,
 
304
    
 
305
    case RemoveDup(SVList,RemoveDup) of
 
306
        [N] ->
 
307
            [{'SingleValue',N}];
 
308
        L when list(L) -> 
 
309
            [{'ValueRange',{hd(L),lists:last(L)}}]
 
310
    end;
 
311
effective_constr('ValueRange',List) ->
 
312
    LBs = lists:map(fun({_,{Lb,_}})-> Lb end,List),
 
313
    UBs = lists:map(fun({_,{_,Ub}})-> Ub end,List),
 
314
    Lb = least_Lb(LBs),
 
315
    [{'ValueRange',{Lb,lists:max(UBs)}}].
 
316
 
 
317
greatest_common_range([],VR) ->
 
318
    VR;
 
319
greatest_common_range(SV,[]) ->
 
320
    SV;
 
321
greatest_common_range([{_,Int}],[{_,{'MIN',Ub}}]) when integer(Int),
 
322
                                                       Int > Ub ->
 
323
    [{'ValueRange',{'MIN',Int}}];
 
324
greatest_common_range([{_,Int}],[{_,{Lb,Ub}}]) when integer(Int),
 
325
                                                    Int < Lb ->
 
326
    [{'ValueRange',{Int,Ub}}];
 
327
greatest_common_range([{_,Int}],VR=[{_,{_Lb,_Ub}}]) when integer(Int) ->
 
328
    VR;
 
329
greatest_common_range([{_,L}],[{_,{Lb,Ub}}]) when list(L) ->
 
330
    Min = least_Lb([Lb|L]),
 
331
    Max = greatest_Ub([Ub|L]),
 
332
    [{'ValueRange',{Min,Max}}].
 
333
    
 
334
 
 
335
least_Lb(L) ->
 
336
    case lists:member('MIN',L) of
 
337
        true -> 'MIN';
 
338
        _ -> lists:min(L)
 
339
    end.
 
340
 
 
341
greatest_Ub(L) ->
 
342
    case lists:member('MAX',L) of
 
343
        true -> 'MAX';
 
344
        _ -> lists:max(L)
 
345
    end.
 
346
 
 
347
 
 
348
get_constraints(L=[{Key,_}],Key) ->
 
349
    L;
 
350
get_constraints([],_) ->
 
351
    [];
 
352
get_constraints(C,Key) ->
 
353
    {value,L} = keysearch_allwithkey(Key,1,C,[]),
 
354
    L.
 
355
 
 
356
keysearch_allwithkey(Key,Ix,C,Acc) ->
 
357
    case lists:keysearch(Key,Ix,C) of
 
358
        false ->
 
359
            {value,Acc};
 
360
        {value,T} ->
 
361
            RestC = lists:delete(T,C),
 
362
            keysearch_allwithkey(Key,Ix,RestC,[T|Acc])
 
363
    end.
 
364
 
260
365
 
261
366
%% Object code generating for encoding and decoding
262
367
%% ------------------------------------------------
302
407
                exit({error,{asn1,{"missing mandatory field in object",
303
408
                                   ObjName}}});
304
409
            {false,'OPTIONAL'} ->
305
 
                EmitFuncClause("_"),
306
 
                emit("   []"),
 
410
                EmitFuncClause("Val"),
 
411
                emit("   [{octets,Val}]"),
307
412
                [];
308
413
            {false,{'DEFAULT',DefaultType}} ->
309
414
                EmitFuncClause("Val"),
338
443
                               ObjName}}});
339
444
        {false,'OPTIONAL'} ->
340
445
            EmitFuncClause("_,_"),
341
 
            emit(["  exit({error,{'use of missing field in object', ",Name,
 
446
            emit(["  exit({error,{'use of missing field in object', ",{asis,Name},
342
447
                  "}})"]);
343
448
        {false,{'DEFAULT',_DefaultObject}} ->
344
449
            exit({error,{asn1,{"not implemented yet",Name}}});
514
619
                exit({error,{asn1,{"missing mandatory field in object",
515
620
                                   ObjName}}});
516
621
            {false,'OPTIONAL'} ->
517
 
                EmitFuncClause("_"),
518
 
                emit(["   asn1_NOVALUE"]),
 
622
                EmitFuncClause("Bytes"),
 
623
                emit(["   {Bytes,[]}"]),
519
624
                [];
520
625
            {false,{'DEFAULT',DefaultType}} ->
521
626
                EmitFuncClause("Bytes"),
549
654
                               ObjName}}});
550
655
        {false,'OPTIONAL'} ->
551
656
            EmitFuncClause("_,_,_"),
552
 
            emit(["  exit({error,{'illegal use of missing field in object', ",Name,
 
657
            emit(["  exit({error,{'illegal use of missing field in object', ",{asis,Name},
553
658
                  "}})"]);
554
659
        {false,{'DEFAULT',_DefaultObject}} ->
555
660
            exit({error,{asn1,{"not implemented yet",Name}}});
783
888
               ClName,ClFields,NthObj,Acc)->
784
889
    emit({"'getenc_",ObjSName,"'(",{asis,UniqueName},",",{asis,Val},
785
890
          ") ->",nl}),
 
891
    CurrMod = get(currmod),
786
892
    {InternalFunc,NewNthObj}=
787
893
        case ObjName of
788
 
            no_name ->
 
894
            {no_mod,no_name} ->
789
895
                gen_inlined_enc_funs(Fields,ClFields,ObjSName,NthObj);
 
896
            {CurrMod,Name} ->
 
897
                emit({"    fun 'enc_",Name,"'/3"}),
 
898
                {[],0};
 
899
            {ModName,Name} ->
 
900
                emit_ext_encfun(ModName,Name),
 
901
%               emit(["    {'",ModName,"', 'enc_",Name,"'}"]),
 
902
                {[],0};
790
903
            _Other ->
791
904
                emit({"    fun 'enc_",ObjName,"'/3"}),
792
905
                {[],0}
799
912
 
800
913
    emit({"'getenc_",ObjSetName,"'(",{asis,UniqueName},",",
801
914
          {asis,Val},") ->",nl}),
 
915
    CurrMod = get(currmod),
802
916
    {InternalFunc,_}=
803
917
        case ObjName of
804
 
            no_name ->
 
918
            {no_mod,no_name} ->
805
919
                gen_inlined_enc_funs(Fields,ClFields,ObjSetName,NthObj);
 
920
            {CurrMod,Name} ->
 
921
                emit({"    fun 'enc_",Name,"'/3"}),
 
922
                {[],NthObj};
 
923
            {ModName,Name} ->
 
924
                emit_ext_encfun(ModName,Name),
 
925
%               emit(["    {'",ModName,"', 'enc_",Name,"'}"]),
 
926
                {[],NthObj};
806
927
            _Other ->
807
928
                emit({"    fun 'enc_",ObjName,"'/3"}),
808
929
                {[],NthObj}
809
930
        end,
 
931
    emit([";",nl]),
 
932
    emit_default_getenc(ObjSetName,UniqueName),
810
933
    emit({".",nl,nl}),
811
934
    InternalFunc++Acc;
812
935
gen_objset_enc(ObjSetName,_UniqueName,['EXTENSIONMARK'],_ClName,
819
942
gen_objset_enc(_,_,[],_,_,_,Acc) ->
820
943
    Acc.
821
944
 
 
945
emit_ext_encfun(ModuleName,Name) ->
 
946
    emit([indent(4),"fun(T,V,O) -> '",ModuleName,"':'enc_",
 
947
          Name,"'(T,V,O) end"]).
 
948
 
 
949
emit_default_getenc(ObjSetName,UniqueName) ->
 
950
    emit(["'getenc_",ObjSetName,"'(",{asis,UniqueName},", _) ->",nl]),
 
951
    emit([indent(4),"fun(C,V,_) -> exit({'Type not compatible with table constraint',{component,C},{value,V}}) end"]).
 
952
 
 
953
 
822
954
%% gen_inlined_enc_funs for each object iterates over all fields of a
823
955
%% class, and for each typefield it checks if the object has that
824
956
%% field and emits the proper code.
939
1071
 
940
1072
    emit({"'getdec_",ObjSName,"'(",{asis,UniqueName},",",{asis,Val},
941
1073
          ") ->",nl}),
 
1074
    CurrMod = get(currmod),
942
1075
    NewNthObj=
943
1076
        case ObjName of
944
 
            no_name ->
 
1077
            {no_mod,no_name} ->
945
1078
                gen_inlined_dec_funs(Fields,ClFields,ObjSName,NthObj);
 
1079
            {CurrMod,Name} ->
 
1080
                emit(["    fun 'dec_",Name,"'/4"]),
 
1081
                NthObj;
 
1082
            {ModName,Name} ->
 
1083
                emit_ext_decfun(ModName,Name),
 
1084
%               emit(["    {'",ModName,"', 'dec_",Name,"'}"]),
 
1085
                NthObj;
946
1086
            _Other ->
947
1087
                emit({"    fun 'dec_",ObjName,"'/4"}),
948
1088
                NthObj
954
1094
 
955
1095
    emit({"'getdec_",ObjSetName,"'(",{asis,UniqueName},",",{asis,Val},
956
1096
          ") ->",nl}),
 
1097
    CurrMod=get(currmod),
957
1098
    case ObjName of
958
 
        no_name ->
 
1099
        {no_mod,no_name} ->
959
1100
            gen_inlined_dec_funs(Fields,ClFields,ObjSetName,NthObj);
 
1101
        {CurrMod,Name} ->
 
1102
            emit(["    fun 'dec_",Name,"'/4"]);
 
1103
        {ModName,Name} ->
 
1104
            emit_ext_decfun(ModName,Name);
 
1105
%           emit(["    {'",ModName,"', 'dec_",Name,"'}"]);
960
1106
        _Other ->
961
1107
            emit({"    fun 'dec_",ObjName,"'/4"})
962
1108
    end,
 
1109
    emit([";",nl]),
 
1110
    emit_default_getdec(ObjSetName,UniqueName),
963
1111
    emit({".",nl,nl}),
964
1112
    ok;
965
1113
gen_objset_dec(ObjSetName,_UniqueName,['EXTENSIONMARK'],_ClName,_ClFields,
973
1121
gen_objset_dec(_,_,[],_,_,_) ->
974
1122
    ok.
975
1123
 
 
1124
emit_ext_decfun(ModuleName,Name) ->
 
1125
    emit([indent(3),"fun(T,V,O1,O2) -> '",ModuleName,"':'dec_",
 
1126
          Name,"'(T,V,O1,O2) end"]).
 
1127
 
 
1128
emit_default_getdec(ObjSetName,UniqueName) ->
 
1129
    emit(["'getdec_",ObjSetName,"'(",{asis,UniqueName},", _) ->",nl]),
 
1130
    emit([indent(2), "fun(C,V,_,_) -> exit({{component,C},{value,V}}) end"]).
 
1131
 
 
1132
 
976
1133
gen_inlined_dec_funs(Fields,[{typefield,Name,_}|Rest],
977
1134
                    ObjSetName,NthObj) ->
978
1135
    CurrMod = get(currmod),
1156
1313
    case Typename of
1157
1314
        'INTEGER' ->
1158
1315
            emit({"?RT_PER:decode_integer(",BytesVar,",",
1159
 
                  {asis,Constraint},")"});
 
1316
                  {asis,effective_constraint(integer,Constraint)},")"});
1160
1317
        {'INTEGER',NamedNumberList} ->
1161
1318
            emit({"?RT_PER:decode_integer(",BytesVar,",",
1162
 
                  {asis,Constraint},",",
 
1319
                  {asis,effective_constraint(integer,Constraint)},",",
1163
1320
                  {asis,NamedNumberList},")"});
1164
1321
        {'BIT STRING',NamedNumberList} ->
1165
1322
            case get(compact_bit_string) of