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

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1ct.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:
26
26
-export([encode/2, encode/3, decode/3]).
27
27
-export([test/1, test/2, test/3, value/2]).
28
28
%% Application internal exports
29
 
-export([compile_asn/3,compile_asn1/3,compile_py/3,compile/3,value/1,vsn/0,
 
29
-export([compile_asn/3,compile_asn1/3,compile_py/3,compile/3,compile_inline/4,
 
30
         value/1,vsn/0,
30
31
         create_ets_table/2,get_name_of_def/1,get_pos_of_def/1]).
31
32
-export([read_config_data/1,get_gen_state_field/1,get_gen_state/0,
32
33
         partial_inc_dec_toptype/1,save_gen_state/1,update_gen_state/2,
84
85
                [ber_bin_v2|Options--[ber_bin]];
85
86
            _ -> Options
86
87
        end,
87
 
    case (catch input_file_type(File)) of
88
 
        {single_file,PrefixedFile} ->
89
 
            (catch compile1(PrefixedFile,Options1));
 
88
    Options2 = includes(File,Options1),
 
89
    Includes=[I||{i,I}<-Options2],
 
90
    case (catch input_file_type(File,Includes)) of
 
91
        {single_file,SuffixedFile} -> %% "e.g. "/tmp/File.asn"
 
92
            (catch compile1(SuffixedFile,Options2));
90
93
        {multiple_files_file,SetBase,FileName} ->
91
 
            FileList = get_file_list(FileName),
92
 
            (catch compile_set(SetBase,filename:dirname(FileName),
93
 
                               FileList,Options1));
 
94
            FileList = get_file_list(FileName,Includes),
 
95
            io:format("FileList: ~p~n",[FileList]),
 
96
            case [X||{inline,X}<-Options2] of
 
97
                [] ->
 
98
                    (catch compile_set(SetBase,filename:dirname(FileName),
 
99
                                       FileList,Options2));
 
100
                [OutputName] -> 
 
101
                    NewFileList=
 
102
                        [filename:rootname(filename:basename(X))||X<-FileList],
 
103
                    (catch compile_inline(OutputName,filename:dirname(FileName),NewFileList,Options2))
 
104
            end;
94
105
        Err = {input_file_error,_Reason} ->
95
 
            {error,Err}
 
106
            {error,Err};
 
107
        Err2 -> Err2
96
108
    end.
97
109
 
98
110
 
106
118
    Includes = [I || {i,I} <- Options],
107
119
    EncodingRule = get_rule(Options),
108
120
    create_ets_table(asn1_functab,[named_table]),
109
 
    Continue1 = scan({true,true},File,Options),
 
121
    Continue1 = scan(File,Options),
110
122
    Continue2 = parse(Continue1,File,Options),
111
123
    Continue3 = check(Continue2,File,OutFile,Includes,EncodingRule,
112
124
                      DbFile,Options,[]),
114
126
    delete_tables([asn1_functab]),
115
127
    compile_erl(Continue4,OutFile,Options).
116
128
 
 
129
                          
117
130
%%****************************************************************************%%
118
131
%% functions dealing with compiling of several input files to one output file %%
119
132
%%****************************************************************************%%
 
133
 
 
134
%%%
 
135
%% compile_inline/3
 
136
%% compiles a number of modules, merges the resulting erlang modules with
 
137
%% the appropriate run-time modules so the resulting module contains all
 
138
%% run-time asn1 functionality. Then compiles the resulting file to beam code.
 
139
%% The merging is done by the igor module. If this function is used in older
 
140
%% versions than R10B the igor module, part of user contribution syntax_tools,
 
141
%% must be provided. It is possible to pass options for the ASN1 compiler
 
142
%% Types:
 
143
%%     Name -> atom()
 
144
%%     Modules -> [filename()]
 
145
%%     Options -> [term()]
 
146
%%     filename() -> file:filename()
 
147
compile_inline(Name,DirName,Modules,Options) ->
 
148
    Options1 =
 
149
        case {lists:member(optimize,Options),lists:member(ber_bin,Options)} of
 
150
            {true,true} -> 
 
151
                [ber_bin_v2|Options--[ber_bin]];
 
152
            _ -> Options
 
153
        end,
 
154
 
 
155
    Fun = fun(M)-> compile(filename:join([DirName,M]),Options1) end,
 
156
    lists:foreach(Fun,Modules),
 
157
    RTmodule = get_runtime_mod(Options1),
 
158
    IgorOptions = igorify_options(remove_asn_flags(Options1)),
 
159
    io:format("*****~nName: ~p~nModules: ~p~nIgorOptions: ~p~n*****",
 
160
              [Name,Modules++RTmodule,IgorOptions]),
 
161
    case catch igor:merge(Name,Modules++RTmodule,[{preprocess,true},{stubs,false}]++IgorOptions) of
 
162
        {'EXIT',{undef,Reason}} -> %% module igor first in R10B
 
163
            io:format("Module igor in syntax_tools must be available:~n~p~n",
 
164
                      [Reason]),
 
165
            {error,'no_compilation'};
 
166
        {'EXIT',_Reason} ->
 
167
            {error,'no_compilation'};
 
168
        _ ->
 
169
            io:format("compiling output module: ~p~n",[Name]),
 
170
            erl_compile(generated_file(Name,IgorOptions),Options1)
 
171
    end.
 
172
 
 
173
%% compile_set/4 merges and compiles a number of asn1 modules
 
174
%% specified in a .set.asn file to one .erl file.
120
175
compile_set(SetBase,DirName,Files,Options) when list(hd(Files)),list(Options) ->
121
176
    %% case when there are several input files in a list
122
177
    io:format("Erlang ASN.1 version ~p compiling ~p ~n",[?vsn,Files]),    
636
691
scan_set(DirName,Files,Options) ->
637
692
    lists:map(
638
693
      fun(F)->
639
 
              case scan({true,true},filename:join([DirName,F]),Options) of
 
694
              case scan(filename:join([DirName,F]),Options) of
640
695
                  {false,{error,Reason}} ->
641
696
                      throw({error,{'scan error in file:',F,Reason}});
642
697
                  {TrueOrFalse,Res} ->
661
716
%%***********************************
662
717
 
663
718
 
664
 
scan({true,_}, File,Options) ->
 
719
scan(File,Options) ->
665
720
    case asn1ct_tok:file(File) of
666
721
        {error,Reason} ->
667
722
            io:format("~p~n",[Reason]),
673
728
                false -> % continue with next pass
674
729
                    {true,Tokens}
675
730
            end
676
 
    end;
677
 
scan({false,Result},_,_) ->
678
 
    Result.
 
731
    end.
679
732
 
680
733
 
681
734
parse({true,Tokens},File,Options) ->
721
774
            cmp(M#module.name,File);
722
775
        _ -> ok
723
776
    end,
724
 
    start(["."|Includes]),
 
777
%    start(["."|Includes]),
 
778
    start(Includes),
725
779
    case asn1ct_check:storeindb(M) of 
726
780
        ok   ->
727
781
            Module = asn1_db:dbget(M#module.name,'MODULE'),
796
850
    Options = S#state.options,
797
851
    SourceDir = S#state.sourcedir,
798
852
    Includes = [I || {i,I} <-Options],
799
 
%    Base = filename:basename(File),
800
853
    Options1 =
801
854
        case {lists:member(optimize,Options),lists:member(ber_bin,Options)} of
802
855
            {true,true} -> 
804
857
            _ -> Options
805
858
        end,
806
859
    
807
 
    case get_input_file(Module,[SourceDir|Includes]) of
808
 
        {file,PrefixedFile} ->
809
 
            case dbfile_uptodate(PrefixedFile,Options1) of
 
860
    case get_input_file(Module,[SourceDir|Includes]) of 
 
861
        %% search for asn1 source
 
862
        {file,SuffixedASN1source} ->
 
863
            case dbfile_uptodate(SuffixedASN1source,Options1) of
810
864
                false ->
811
 
                    parse_and_save1(PrefixedFile,Options1);
 
865
                    parse_and_save1(SuffixedASN1source,Options1,Includes);
812
866
                _ -> ok
813
867
            end;
814
868
        Err ->
 
869
            io:format("Warning: could not do a consistency check of the ~p file: no asn1 source file was found.~n",[lists:concat([Module,".asn1db"])]),
815
870
            {error,{asn1,input_file_error,Err}}
816
871
    end.
817
 
parse_and_save1(File,Options) ->
 
872
parse_and_save1(File,Options,Includes) ->
818
873
    Ext = filename:extension(File),
819
874
    Base = filename:basename(File,Ext),
820
875
    DbFile = outfile(Base,"asn1db",Options),
821
 
    Includes = [I || {i,I} <- Options],
822
 
    Continue1 = scan({true,true},File,Options),
 
876
    Continue1 = scan(File,Options),
823
877
    M =
824
878
        case parse(Continue1,File,Options) of
825
879
            {true,Mod} -> Mod;
826
880
            _ ->
827
 
                exit({error,{asn1,File,"no such file or directory"}})
 
881
%%              io:format("~p~nnow I die!!!!!!!!!!!~n",[File]),
 
882
                exit({error,{asn1,File,"no such file"}})
828
883
        end,
829
 
    start(["."|Includes]),
 
884
%    start(["."|Includes]),
 
885
    start(Includes),
830
886
    case asn1ct_check:storeindb(M) of 
831
887
        ok   ->
832
888
            asn1_db:dbsave(DbFile,M#module.name)
837
893
get_input_file(Module,[I|Includes]) ->
838
894
    case (catch input_file_type(filename:join([I,Module]))) of
839
895
        {single_file,FileName} ->
840
 
            case file:read_file_info(FileName) of
841
 
                {ok,_} ->
 
896
%%          case file:read_file_info(FileName) of
 
897
%%              {ok,_} ->
842
898
                    {file,FileName};
843
 
                _ -> get_input_file(Module,Includes)
844
 
            end;
 
899
%%              _ -> get_input_file(Module,Includes)
 
900
%%          end;
845
901
        _ -> 
846
902
            get_input_file(Module,Includes)
847
903
    end.
854
910
    case file:read_file_info(DbFile) of
855
911
        {error,enoent} ->
856
912
            false;
857
 
%       {error,Reason} ->
858
 
%           io:format("Reason:~n~p~n",[Reason]);
859
913
        {ok,FileInfoDb} ->
860
914
            %% file exists, check date and finally encodingrule
861
915
            {ok,FileInfoAsn} = file:read_file_info(File),
897
951
compile_erl({false,Result},_,_) ->
898
952
    Result.
899
953
 
 
954
input_file_type(Name,I) ->
 
955
   case input_file_type(Name) of
 
956
       {error,_} -> input_file_type2(filename:basename(Name),I);
 
957
       Err={input_file_error,_} -> Err;
 
958
       Res -> Res
 
959
   end.
 
960
input_file_type2(Name,[I|Is]) ->
 
961
    case input_file_type(filename:join([I,Name])) of
 
962
        {error,_} -> input_file_type2(Name,Is);
 
963
        Err={input_file_error,_} -> Err;
 
964
        Res -> Res
 
965
    end;
 
966
input_file_type2(Name,[]) ->
 
967
    input_file_type(Name).
 
968
           
900
969
input_file_type([]) ->
901
970
    {empty_name,[]};
902
971
input_file_type(File) ->
910
979
                        {ok,_FileInfo} ->
911
980
                            {single_file, lists:concat([File,".asn"])};
912
981
                        _Error ->
913
 
                            {single_file, lists:concat([File,".py"])}
 
982
                            case file:read_file_info(lists:concat([File,".py"])) of
 
983
                                {ok,_FileInfo} ->
 
984
                                    {single_file, lists:concat([File,".py"])};
 
985
                                Error ->
 
986
                                    Error
 
987
                            end
914
988
                    end
915
989
            end;
916
990
        ".asn1config" ->
917
991
            case read_config_file(File,asn1_module) of
918
992
                {ok,Asn1Module} -> 
919
 
                    put(asn1_config_file,File),
 
993
%                   put(asn1_config_file,File),
920
994
                    input_file_type(Asn1Module);
921
995
                Error ->
922
996
                    Error
923
997
            end;
924
 
        Asn1PFix ->
925
 
            Base = filename:basename(File,Asn1PFix),
926
 
            case filename:extension(Base) of
927
 
                [] ->
928
 
                    {single_file,File};
929
 
                SetPFix when (SetPFix == ".set") ->
930
 
                    {multiple_files_file,
931
 
                     list_to_atom(filename:basename(Base,SetPFix)),
932
 
                     File};
933
 
                _Error ->
934
 
                    throw({input_file_error,{'Bad input file',File}})
 
998
        Asn1SFix ->
 
999
            Base = filename:basename(File,Asn1SFix),
 
1000
            Ret =
 
1001
                case filename:extension(Base) of
 
1002
                    [] ->
 
1003
                        {single_file,File};
 
1004
                    SetSFix when (SetSFix == ".set") ->
 
1005
                        {multiple_files_file,
 
1006
                         list_to_atom(filename:basename(Base,SetSFix)),
 
1007
                         File};
 
1008
                    _Error ->
 
1009
                        throw({input_file_error,{'Bad input file',File}})
 
1010
                end,
 
1011
            %% check that the file exists
 
1012
            case file:read_file_info(File) of
 
1013
                {ok,_} -> Ret;
 
1014
                Err -> Err
935
1015
            end
936
1016
    end.
937
1017
 
938
 
get_file_list(File) ->
 
1018
get_file_list(File,Includes) ->
939
1019
    case file:open(File,read) of
940
1020
        {error,Reason} ->
941
1021
            {error,{File,file:format_error(Reason)}};
942
1022
        {ok,Stream} ->
943
 
            get_file_list1(Stream,[])
 
1023
            get_file_list1(Stream,filename:dirname(File),Includes,[])
944
1024
    end.
945
1025
 
946
 
get_file_list1(Stream,Acc) ->
 
1026
get_file_list1(Stream,Dir,Includes,Acc) ->
947
1027
    Ret = io:get_line(Stream,''),
948
1028
    case Ret of
949
1029
        eof ->
950
1030
            file:close(Stream),
951
1031
            lists:reverse(Acc);
952
1032
        FileName ->
953
 
            PrefixedNameList =
954
 
                case (catch input_file_type(lists:delete($\n,FileName))) of
 
1033
            SuffixedNameList =
 
1034
                case (catch input_file_type(filename:join([Dir,lists:delete($\n,FileName)]),Includes)) of
955
1035
                    {empty_name,[]} -> [];
956
1036
                    {single_file,Name} -> [Name];
957
 
                    {multiple_files_file,Name} ->
958
 
                        get_file_list(Name);
959
 
                    Err = {input_file_error,_Reason} ->
960
 
                        throw(Err)
 
1037
                    {multiple_files_file,_,Name} ->
 
1038
                        get_file_list(Name,Includes);
 
1039
                    _Err ->
 
1040
                        []
961
1041
                end,
962
 
            get_file_list1(Stream,PrefixedNameList++Acc)
 
1042
            get_file_list1(Stream,Dir,Includes,SuffixedNameList++Acc)
963
1043
    end.
964
1044
 
965
1045
get_rule(Options) ->
974
1054
            ber
975
1055
    end.
976
1056
 
 
1057
get_runtime_mod(Options) ->
 
1058
    RtMod1=
 
1059
        case get_rule(Options) of
 
1060
            per -> ["asn1rt_per_v1.erl"];
 
1061
            ber -> ["asn1rt_ber_bin.erl"];
 
1062
            per_bin ->
 
1063
                case lists:member(optimize,Options) of
 
1064
                    true -> ["asn1rt_per_bin_rt2ct.erl"];
 
1065
                    _ -> ["asn1rt_per_bin.erl"]
 
1066
                end;
 
1067
            ber_bin -> ["asn1rt_ber_bin.erl"];
 
1068
            ber_bin_v2 -> ["asn1rt_ber_bin_v2.erl"]
 
1069
        end,
 
1070
    RtMod1++["asn1rt_check.erl","asn1rt_driver_handler.erl"].
 
1071
    
 
1072
 
977
1073
erl_compile(OutFile,Options) ->
978
1074
%    io:format("Options:~n~p~n",[Options]),
979
1075
    case lists:member(noobj,Options) of
995
1091
          X /= optimize,
996
1092
          X /= compact_bit_string,
997
1093
          X /= debug,
998
 
          X /= keyed_list].
 
1094
          X /= keyed_list,
 
1095
          X /= asn1config].
999
1096
          
1000
1097
debug_on(Options) ->
1001
1098
    case lists:member(debug,Options) of
1011
1108
            true
1012
1109
    end.
1013
1110
 
 
1111
igorify_options(Options) ->
 
1112
    case lists:keysearch(outdir,1,Options) of
 
1113
        {value,{_,Dir}} ->
 
1114
            Options1 = lists:keydelete(outdir,1,Options),
 
1115
            [{dir,Dir}|Options1];
 
1116
        _ ->
 
1117
            Options
 
1118
    end.
 
1119
 
 
1120
generated_file(Name,Options) ->
 
1121
    case lists:keysearch(dir,1,Options) of
 
1122
        {value,{_,Dir}} ->
 
1123
            filename:join([Dir,filename:basename(Name)]);
 
1124
        _ ->
 
1125
            Name
 
1126
    end.
1014
1127
 
1015
1128
debug_off(_Options) ->
1016
1129
    erase(asndebug),
1017
1130
    erase(asn_keyed_list).
1018
1131
 
1019
1132
 
1020
 
outfile(Base, Ext, Opts) when atom(Ext) ->
1021
 
    outfile(Base, atom_to_list(Ext), Opts);
1022
1133
outfile(Base, Ext, Opts) ->
 
1134
%    io:format("Opts. ~p~n",[Opts]),
1023
1135
    Obase = case lists:keysearch(outdir, 1, Opts) of
1024
1136
                {value, {outdir, Odir}} -> filename:join(Odir, Base);
1025
1137
                _NotFound -> Base % Not found or bad format
1031
1143
            lists:concat([Obase,".",Ext])
1032
1144
    end.
1033
1145
 
 
1146
includes(File,Options) -> 
 
1147
    case filename:dirname(File) of
 
1148
        [] ->
 
1149
            Options;
 
1150
        Dir ->
 
1151
            Options2 =
 
1152
                case lists:member({i,"."},Options) of
 
1153
                    false -> Options ++ [{i,"."}];
 
1154
                    _ -> Options
 
1155
                end,
 
1156
            case lists:member({i,Dir}, Options) of
 
1157
                false -> Options2 ++ [{i,Dir}];
 
1158
                _ -> Options2
 
1159
            end
 
1160
    end.
 
1161
 
1034
1162
%% compile(AbsFileName, Options)
1035
1163
%%   Compile entry point for erl_compile.
1036
1164
 
1437
1565
%             [CommandList,SelectedDecode]),
1438
1566
    CommandList2 = 
1439
1567
        create_partial_inc_decode_gen_info(M#module.name,ExclusiveDecode),
1440
 
%%    io:format("partial_incomplete_decode = ~p~n",[CommandList2]),
 
1568
%    io:format("partial_incomplete_decode = ~p~n",[CommandList2]),
1441
1569
    Part_inc_tlv_tags = tag_format(ber_bin_v2,Options,CommandList2),
1442
1570
%    io:format("partial_incomplete_decode: tlv_tags = ~p~n",[Part_inc_tlv_tags]),
1443
1571
    save_config(partial_incomplete_decode,Part_inc_tlv_tags),
1951
2079
    end.
1952
2080
    
1953
2081
get_config_info(CfgList,InfoType) ->
1954
 
    case InfoType of
1955
 
        all ->
1956
 
            CfgList;
1957
 
        _ ->
1958
 
            case lists:keysearch(InfoType,1,CfgList) of
1959
 
                {value,{InfoType,Value}} ->
1960
 
                    Value;
1961
 
                false ->
1962
 
                    []
1963
 
            end
 
2082
    case lists:keysearch(InfoType,1,CfgList) of
 
2083
        {value,{InfoType,Value}} ->
 
2084
            Value;
 
2085
        false ->
 
2086
            []
1964
2087
    end.
1965
2088
 
1966
2089
%% save_config/2 saves the Info with the key Key
2250
2373
 
2251
2374
%% adds Data to gen_refed_funcs field in gen_state.
2252
2375
add_generated_refed_func(Data) ->
2253
 
    L = get_gen_state_field(gen_refed_funcs),
2254
 
    update_gen_state(gen_refed_funcs,[Data|L]).
 
2376
    case is_function_generated(Data) of
 
2377
        true ->
 
2378
            ok;
 
2379
        _ ->
 
2380
            L = get_gen_state_field(gen_refed_funcs),
 
2381
            update_gen_state(gen_refed_funcs,[Data|L])
 
2382
    end.
2255
2383
 
2256
2384
next_refed_func() ->
2257
2385
    case get_gen_state_field(tobe_refed_funcs) of
2415
2543
                _ -> false
2416
2544
            end
2417
2545
    end.
2418
 
%           Pred =
2419
 
%               fun({N,_,_}) when N==Name ->
2420
 
%                       true;
2421
 
%                  (_) -> false
2422
 
%               end,
2423
 
%           L2 = lists:filter(Pred,L),
2424
 
%           case lists:keysearch(Pattern,3,L2) of
2425
 
%               false ->
2426
 
%                   false;
2427
 
%               {value,{_,SI,_}} -> SI
2428
 
%           end
2429
 
%     end.
2430
2546
    
2431
2547
next_sindex() ->
2432
2548
    SI = get_gen_state_field(suffix_index),