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

« back to all changes in this revision

Viewing changes to lib/asn1/test/test_compile_options.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2005-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
 
 
21
-module(test_compile_options).
 
22
 
 
23
-include_lib("test_server/include/test_server.hrl").
 
24
 
 
25
 
 
26
-export([wrong_path/1,comp/2,path/1,ticket_6143/1,noobj/1,
 
27
         record_name_prefix/1,verbose/1]).
 
28
 
 
29
%% OTP-5689
 
30
wrong_path(Config) ->
 
31
    Pid=spawn(?MODULE,comp,[self(),Config]),
 
32
    receive
 
33
        _Err ->
 
34
            ok
 
35
    after 10000 ->
 
36
            exit(Pid,failure),
 
37
            error
 
38
    end.
 
39
 
 
40
comp(Parent,Config) ->
 
41
    DataDir = ?config(data_dir,Config),
 
42
    OutDir = ?config(priv_dir,Config),
 
43
    %%?line true = code:add_patha(?config(priv_dir,Config)),
 
44
    io:format("DataDir: ~p~n",[DataDir]),
 
45
    ?line Err=asn1ct:compile(DataDir++"NoImport",[{i,OutDir},{i,filename:join([DataDir,"subdir"])},{outdir,OutDir}]),
 
46
    io:format("compiling process terminated with value: ~p~n",[Err]),
 
47
    Parent!Err.
 
48
 
 
49
%% OTP-5701
 
50
 
 
51
path(Config) ->
 
52
    DataDir = ?config(data_dir,Config),
 
53
    OutDir = ?config(priv_dir,Config),
 
54
    {ok,CWD} = file:get_cwd(),
 
55
    ?line file:set_cwd(filename:join([DataDir,subdir])),
 
56
 
 
57
    %%?line ok=asn1ct:compile(filename:join([DataDir,"../MyMerge.set.asn"]),[{inline,mymerge},{outdir,OutDir}]),
 
58
    ?line ok=asn1ct:compile("../MyMerge.set.asn",[{inline,mymerge},{outdir,OutDir}]),
 
59
 
 
60
    ?line ok=outfiles_check(OutDir),
 
61
    ?line outfiles_remove(OutDir),
 
62
 
 
63
    file:set_cwd(filename:join([DataDir,subdir,subsubdir])),
 
64
    ?line ok = asn1ct:compile('../../MyMerge.set.asn',[{inline,mymerge},{i,'..'},{outdir,OutDir}]),
 
65
 
 
66
    ?line ok=outfiles_check(OutDir,outfiles2()),
 
67
    file:set_cwd(CWD),
 
68
    ok.
 
69
 
 
70
ticket_6143(Config) ->
 
71
    DataDir = ?config(data_dir,Config),
 
72
    OutDir = ?config(priv_dir,Config),
 
73
    io:format("DataDir: ~p~n",[DataDir]),
 
74
 
 
75
    ?line ok=asn1ct:compile(filename:join([DataDir,"AA1"]),[{i,DataDir},{outdir,OutDir}]),
 
76
    ok.
 
77
 
 
78
noobj(Config) ->
 
79
    DataDir = ?config(data_dir,Config),
 
80
    OutDir = ?config(priv_dir,Config),
 
81
    
 
82
    code:purge('P-Record'),
 
83
    file:delete(filename:join([OutDir,'P-Record.erl'])),
 
84
    file:delete(filename:join([OutDir,'P-Record.beam'])),
 
85
    ?line ok=asn1ct:compile(filename:join([DataDir,"P-Record"]),
 
86
                            [noobj,{outdir,OutDir}]),
 
87
%    ?line false = code:is_loaded('P-Record'),
 
88
    ?line {ok,_} = file:read_file_info(filename:join([OutDir,
 
89
                                                      "P-Record.erl"])),
 
90
    ?line {error,enoent} =
 
91
        file:read_file_info(filename:join([OutDir,"P-Record.beam"])),
 
92
    ?line {ok,_} = c:c(filename:join([OutDir,'P-Record']),
 
93
                       [{i,OutDir},{outdir,OutDir}]),
 
94
    ?line {file,_} = code:is_loaded('P-Record'),
 
95
    
 
96
    code:purge('P-Record'),
 
97
    code:delete('P-Record'),
 
98
    code:purge('p_record'),
 
99
    code:delete('p_record'),
 
100
    file:delete(filename:join([OutDir,'P-Record.erl'])),
 
101
    file:delete(filename:join([OutDir,'P-Record.beam'])),
 
102
    file:delete(filename:join([OutDir,'p_record.erl'])),
 
103
    file:delete(filename:join([OutDir,'p_record.beam'])),
 
104
    ?line ok=asn1ct:compile(filename:join([DataDir,"p_record.set.asn"]),[asn1config,ber_bin,optimize,noobj,{outdir,OutDir}]),
 
105
%%     ?line false = code:is_loaded('P-Record'),
 
106
%%     ?line false = code:is_loaded('p_record'),
 
107
    ?line {error,enoent} =
 
108
        file:read_file_info(filename:join([OutDir,"P-Record.beam"])),
 
109
    ?line {error,enoent} =
 
110
        file:read_file_info(filename:join([OutDir,"P-Record.erl"])),
 
111
    ?line {error,enoent} =
 
112
        file:read_file_info(filename:join([OutDir,"p_record.beam"])),
 
113
    io:format("read_file_info: p_record.erl~n",[]),
 
114
    ?line {ok,_} =
 
115
        file:read_file_info(filename:join([OutDir,"p_record.erl"])),
 
116
    io:format("c:c: p_record.erl~n",[]),
 
117
    ?line {ok,_} = c:c(filename:join([OutDir,'p_record']),
 
118
                       [{i,OutDir},{outdir,OutDir}]),
 
119
    io:format("code:is_loaded: p_record.erl~n",[]),
 
120
    ?line {file,_} = code:is_loaded('p_record'),
 
121
    io:format("file:delete: p_record.erl~n",[]),
 
122
    file:delete(filename:join([OutDir,'p_record.erl'])),
 
123
    file:delete(filename:join([OutDir,'p_record.beam'])).
 
124
 
 
125
verbose(Config) when is_list(Config) ->
 
126
    DataDir = ?config(data_dir,Config),
 
127
    OutDir = ?config(priv_dir,Config),
 
128
    Asn1File = filename:join([DataDir,"Comment.asn"]),
 
129
 
 
130
    %% Test verbose compile
 
131
    ?line test_server:capture_start(),
 
132
    ?line ok = asn1ct:compile(Asn1File, [{i,DataDir},{outdir,OutDir},noobj,verbose]),
 
133
    ?line test_server:capture_stop(),
 
134
    ?line [Line0|_] = test_server:capture_get(),
 
135
    ?line true = lists:prefix("Erlang ASN.1 version", Line0),
 
136
 
 
137
    %% Test non-verbose compile
 
138
    ?line test_server:capture_start(),
 
139
    ?line ok = asn1ct:compile(Asn1File, [{i,DataDir},{outdir,OutDir},noobj]),
 
140
    ?line test_server:capture_stop(),
 
141
    ?line [] = test_server:capture_get(),
 
142
    ok.
 
143
 
 
144
outfiles_check(OutDir) ->
 
145
    outfiles_check(OutDir,outfiles1()).
 
146
 
 
147
 
 
148
outfiles_check(_OutDir,[])->
 
149
    ok;
 
150
outfiles_check(OutDir,[H|T]) ->
 
151
    io:format("File: ~p~n",[filename:join([OutDir,H])]),
 
152
    ?line {ok,_}=file:read_file_info(filename:join([OutDir,H])),
 
153
    outfiles_check(OutDir,T).
 
154
 
 
155
outfiles1() ->
 
156
    ["mymerge.erl","mymerge.beam","MyMerge.asn1db","MyMerge.beam",
 
157
     "MyMerge.erl","MyMerge.hrl"].
 
158
outfiles2() ->
 
159
    ["MyMerge.beam","mymerge.erl","MyMerge.asn1db","MyMerge.erl",
 
160
     "mymerge.beam"].
 
161
 
 
162
outfiles_remove(OutDir) ->
 
163
    lists:foreach(fun(F)-> file:delete(filename:join([OutDir,F])) end,
 
164
                  outfiles1()).
 
165
 
 
166
record_name_prefix(Config) ->
 
167
    DataDir = ?config(data_dir,Config),
 
168
    OutDir = ?config(priv_dir,Config),
 
169
    ok = b_SeqIn(DataDir,OutDir),
 
170
    ok = a_SeqIn(DataDir,OutDir).
 
171
 
 
172
b_SeqIn(DataDir,OutDir) ->
 
173
    asn1ct:compile(filename:join([DataDir,'Seq']),
 
174
                   [{record_name_prefix,"b_"},{outdir,OutDir}]),
 
175
    io:format("FileName: ~p~nOutDir:~p~n",
 
176
              [filename:join([DataDir,'b_SeqIn']),OutDir]),
 
177
    ?line {ok,_} = compile:file(filename:join([DataDir,'b_SeqIn']),
 
178
                          [{i,OutDir}]),
 
179
    ?line 'b_SeqIn' = b_SeqIn:record_name(),
 
180
    ok.
 
181
 
 
182
a_SeqIn(DataDir,OutDir) -> 
 
183
    asn1ct:compile(filename:join([DataDir,'Seq']),
 
184
                   [{record_name_prefix,"a_"},{outdir,OutDir}]),
 
185
    ?line {ok,_} = compile:file(filename:join([DataDir,'a_SeqIn']),
 
186
                          [{i,OutDir}]),
 
187
    ?line 'a_SeqIn' = a_SeqIn:record_name(),
 
188
    ok.