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

« back to all changes in this revision

Viewing changes to lib/asn1/src/asn1ct.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-2011. 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
%%
39
39
         add_tobe_refed_func/1,add_generated_refed_func/1,
40
40
         maybe_rename_function/3,latest_sindex/0,current_sindex/0,
41
41
         set_current_sindex/1,next_sindex/0,maybe_saved_sindex/2,
42
 
         parse_and_save/2]).
 
42
         parse_and_save/2,verbose/3,warning/3,error/3]).
43
43
 
44
44
-include("asn1_records.hrl").
45
45
-include_lib("stdlib/include/erl_compile.hrl").
103
103
 
104
104
 
105
105
compile1(File,Options) when is_list(Options) ->
106
 
    io:format("Erlang ASN.1 version ~p compiling ~p ~n",[?vsn,File]),
107
 
    io:format("Compiler Options: ~p~n",[Options]),
 
106
    verbose("Erlang ASN.1 version ~p compiling ~p ~n",[?vsn,File],Options),
 
107
    verbose("Compiler Options: ~p~n",[Options],Options),
108
108
    Ext = filename:extension(File),
109
109
    Base = filename:basename(File,Ext),
110
110
    OutFile = outfile(Base,"",Options),
149
149
inline(true,Name,Module,Options) ->
150
150
    RTmodule = get_runtime_mod(Options),
151
151
    IgorOptions = igorify_options(remove_asn_flags(Options)),
152
 
    IgorName = filename:rootname(filename:basename(Name)),
 
152
    IgorName = list_to_atom(filename:rootname(filename:basename(Name))),
153
153
%    io:format("*****~nName: ~p~nModules: ~p~nIgorOptions: ~p~n*****~n",
154
154
%             [IgorName,Modules++RTmodule,IgorOptions]),
155
 
    io:format("Inlining modules: ~p in ~p~n",[[Module]++RTmodule,IgorName]),
 
155
    verbose("Inlining modules: ~p in ~p~n",[[Module]++RTmodule,IgorName],Options),
156
156
    case catch igor:merge(IgorName,[Module]++RTmodule,[{preprocess,true},{stubs,false},{backups,false}]++IgorOptions) of
157
157
        {'EXIT',{undef,Reason}} -> %% module igor first in R10B
158
 
            io:format("Module igor in syntax_tools must be available:~n~p~n",
159
 
                      [Reason]),
 
158
            error("Module igor in syntax_tools must be available:~n~p~n",
 
159
                  [Reason],Options),
160
160
            {error,'no_compilation'};
161
161
        {'EXIT',Reason} ->
162
 
            io:format("Merge by igor module failed due to ~p~n",[Reason]),
 
162
            error("Merge by igor module failed due to ~p~n",[Reason],Options),
163
163
            {error,'no_compilation'};
164
164
        _ ->
165
165
%%          io:format("compiling output module: ~p~n",[generated_file(Name,IgorOptions)]),
173
173
compile_set(SetBase,Files,Options) 
174
174
  when is_list(hd(Files)),is_list(Options) ->
175
175
    %% case when there are several input files in a list
176
 
    io:format("Erlang ASN.1 version ~p compiling ~p ~n",[?vsn,Files]),    
177
 
    io:format("Compiler Options: ~p~n",[Options]),
 
176
    verbose("Erlang ASN.1 version ~p compiling ~p ~n",[?vsn,Files],Options),
 
177
    verbose("Compiler Options: ~p~n",[Options],Options),
178
178
    OutFile = outfile(SetBase,"",Options),
179
179
    DbFile = outfile(SetBase,"asn1db",Options),
180
180
    Includes = [I || {i,I} <- Options],
728
728
scan(File,Options) ->
729
729
    case asn1ct_tok:file(File) of
730
730
        {error,Reason} ->
731
 
            io:format("~p~n",[Reason]),
 
731
            error("~p~n",[Reason],Options),
732
732
            {false,{error,Reason}};
733
733
        Tokens ->
734
734
            case lists:member(ss,Options) of
753
753
            if 
754
754
                is_integer(Line) ->
755
755
                    BaseName = filename:basename(File),
756
 
                    io:format("syntax error at line ~p in module ~s:~n",
757
 
                              [Line,BaseName]);
 
756
                    error("syntax error at line ~p in module ~s:~n",
 
757
                          [Line,BaseName],Options);
758
758
                true ->
759
 
                    io:format("syntax error in module ~p:~n",[File])
 
759
                    error("syntax error in module ~p:~n",
 
760
                          [File],Options)
760
761
            end,
761
762
            print_error_message(Message),
762
763
            {false,{error,Message}};
763
764
        {error,{Line,_Mod,[Message,Token]}} ->
764
 
            io:format("syntax error: ~p ~p at line ~p~n",
765
 
                      [Message,Token,Line]),
 
765
            error("syntax error: ~p ~p at line ~p~n",
 
766
                  [Message,Token,Line],Options),
766
767
            {false,{error,{Line,[Message,Token]}}};
767
768
        {ok,M} ->
768
769
            case lists:member(sp,Options) of
772
773
                    {true,M}
773
774
            end;
774
775
        OtherError ->
775
 
            io:format("~p~n",[OtherError])
 
776
            error("~p~n",[OtherError],Options)
776
777
    end;
777
778
parse({false,Tokens},_,_) ->
778
779
    {false,Tokens}.
802
803
                    NewM = Module#module{typeorval=NewTypeOrVal},
803
804
                    asn1_db:dbput(NewM#module.name,'MODULE',NewM),
804
805
                    asn1_db:dbsave(DbFile,M#module.name),
805
 
                    io:format("--~p--~n",[{generated,DbFile}]),
 
806
                    verbose("--~p--~n",[{generated,DbFile}],Options),
806
807
                    {true,{M,NewM,GenTypeOrVal}}
807
808
            end
808
809
    end;
823
824
%    io:format("Options: ~p~n",[Options]),
824
825
    case catch specialized_decode_prepare(EncodingRule,M,GenTOrV,Options) of
825
826
        {error, enoent} -> ok;
826
 
        {error, Reason} -> io:format("WARNING: Error in configuration"
827
 
                                     "file: ~n~p~n",[Reason]);
828
 
        {'EXIT',Reason} -> io:format("WARNING: Internal error when "
829
 
                                     "analyzing configuration"
830
 
                                     "file: ~n~p~n",[Reason]);
 
827
        {error, Reason} -> warning("Error in configuration "
 
828
                                   "file: ~n~p~n",[Reason],Options);
 
829
        {'EXIT',Reason} -> warning("Internal error when "
 
830
                                   "analyzing configuration "
 
831
                                   "file: ~n~p~n",[Reason],Options);
831
832
        _ -> ok
832
833
    end,
833
834
 
834
835
    Result = 
835
836
        case (catch asn1ct_gen:pgen(OutFile,EncodingRule,
836
 
                                   M#module.name,GenTOrV)) of
 
837
                                   M#module.name,GenTOrV,Options)) of
837
838
            {'EXIT',Reason2} ->
838
 
                io:format("ERROR: ~p~n",[Reason2]),
 
839
                error("~p~n",[Reason2],Options),
839
840
                {error,Reason2};
840
841
            _ ->
841
842
                ok
878
879
                _ -> ok
879
880
            end;
880
881
        Err ->
881
 
            io:format("Warning: could not do a consistency check of the ~p file: no asn1 source file was found.~n",[lists:concat([Module,".asn1db"])]),
 
882
            warning("could not do a consistency check of the ~p file: no asn1 source file was found.~n",
 
883
                    [lists:concat([Module,".asn1db"])],Options),
882
884
            {error,{asn1,input_file_error,Err}}
883
885
    end.
884
886
parse_and_save1(S,File,Options,Includes) ->
1183
1185
        _ ->
1184
1186
            lists:keymember(inline,1,Options)
1185
1187
    end.
 
1188
 
1186
1189
inline_output(Options,Default) ->
1187
1190
    case [X||{inline,X}<-Options] of
1188
1191
        [OutputName] ->
1207
1210
compile(File, _OutFile, Options) ->
1208
1211
    case catch compile(File, make_erl_options(Options)) of
1209
1212
        Exit = {'EXIT',_Reason} ->
1210
 
            io:format("~p~n~s~n",[Exit,"error"]),
 
1213
            error("~p~n~s~n",[Exit,"error"],Options),
1211
1214
            error;
1212
1215
        {error,_Reason} ->
1213
1216
            %% case occurs due to error in asn1ct_parser2,asn1ct_check
1215
1218
%%          io:format("~p~n~s~n",[_Reason,"error"]),
1216
1219
            error;
1217
1220
        ok -> 
1218
 
            io:format("ok~n"),
1219
1221
            ok;
1220
1222
        ParseRes when is_tuple(ParseRes) ->
1221
1223
            io:format("~p~n",[ParseRes]),
1224
1226
            io:format("~p~n",[ScanRes]),
1225
1227
            ok;
1226
1228
        Unknown -> 
1227
 
            io:format("~p~n~s~n",[Unknown,"error"]),
 
1229
            error("~p~n~s~n",[Unknown,"error"],Options),
1228
1230
            error
1229
1231
    end.
1230
1232
 
1238
1240
    Includes = Opts#options.includes,
1239
1241
    Defines = Opts#options.defines,
1240
1242
    Outdir = Opts#options.outdir,
1241
 
%%    Warning = Opts#options.warning,
 
1243
    Warning = Opts#options.warning,
1242
1244
    Verbose = Opts#options.verbose,
1243
1245
    Specific = Opts#options.specific,
1244
1246
    Optimize = Opts#options.optimize,
1250
1252
            true ->  [verbose];
1251
1253
            false -> []
1252
1254
        end ++
1253
 
%%%     case Warning of
1254
 
%%%         0 -> [];
1255
 
%%%         _ -> [report_warnings]
1256
 
%%%     end ++
 
1255
        case Warning of
 
1256
            0 -> [];
 
1257
            _ -> [warnings]
 
1258
        end ++
1257
1259
        [] ++
1258
1260
        case Optimize of
1259
1261
            1 -> [optimize];
1277
1279
            uper_bin -> [uper_bin]
1278
1280
        end,
1279
1281
 
1280
 
    Options++[report_errors, {cwd, Cwd}, {outdir, Outdir}|
 
1282
    Options++[errors, {cwd, Cwd}, {outdir, Outdir}|
1281
1283
              lists:map(fun(Dir) -> {i, Dir} end, Includes)]++Specific.
1282
1284
 
1283
1285
pretty2(Module,AbsFile) ->
1675
1677
%                            [concat_sequential(lists:reverse(Comms),
1676
1678
%                                              [LastComm,CompAcc])|Acc]
1677
1679
                             case lists:reverse(TagCommand) of
1678
 
                                 [Atom|Comms]�when is_atom(Atom) ->
 
1680
                                 [Atom|Comms] when is_atom(Atom) ->
1679
1681
                                     [concat_sequential(lists:reverse(Comms),
1680
1682
                                                        [Atom,CompAcc])|Acc];
1681
1683
                                 [[Command2,Tag2]|Comms] ->
2518
2520
     lists:concat(["_",I]);
2519
2521
 make_suffix(_) ->
2520
2522
     "".
 
2523
 
 
2524
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
2525
%% Report functions.
 
2526
%%
 
2527
%% Errors messages are controlled with the 'errors' compiler option
 
2528
%% Warning messages are controlled with the 'warnings' compiler option
 
2529
%% Verbose messages are controlled with the 'verbose' compiler option
 
2530
 
 
2531
error(Format, Args, S) ->
 
2532
    case is_error(S) of
 
2533
        true ->
 
2534
            io:format("Error: " ++ Format, Args);
 
2535
        false ->
 
2536
            ok
 
2537
    end.
 
2538
 
 
2539
warning(Format, Args, S) ->
 
2540
    case is_warning(S) of
 
2541
        true ->
 
2542
            io:format("Warning: " ++ Format, Args);
 
2543
        false ->
 
2544
            ok
 
2545
    end.
 
2546
 
 
2547
verbose(Format, Args, S) ->
 
2548
    case is_verbose(S) of
 
2549
        true ->
 
2550
            io:format(Format, Args);
 
2551
        false ->
 
2552
            ok
 
2553
    end.
 
2554
 
 
2555
is_error(S) when is_record(S, state) ->
 
2556
    is_error(S#state.options);
 
2557
is_error(O) ->
 
2558
    lists:member(errors, O) orelse is_verbose(O).
 
2559
 
 
2560
is_warning(S) when is_record(S, state) ->
 
2561
    is_warning(S#state.options);
 
2562
is_warning(O) ->
 
2563
    lists:member(warnings, O) orelse is_verbose(O).
 
2564
 
 
2565
is_verbose(S) when is_record(S, state) ->
 
2566
    is_verbose(S#state.options);
 
2567
is_verbose(O) ->
 
2568
    lists:member(verbose, O).