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

« back to all changes in this revision

Viewing changes to lib/asn1/test/asn1_app_test.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
%% Purpose: Verify the application specifics of the asn1 application
 
22
%%----------------------------------------------------------------------
 
23
-module(asn1_app_test).
 
24
 
 
25
-compile(export_all).
 
26
 
 
27
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
28
 
 
29
all() -> 
 
30
    [fields, modules, exportall, app_depend].
 
31
 
 
32
groups() -> 
 
33
    [].
 
34
 
 
35
init_per_group(_GroupName, Config) ->
 
36
        Config.
 
37
 
 
38
end_per_group(_GroupName, Config) ->
 
39
        Config.
 
40
 
 
41
 
 
42
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
43
 
 
44
init_per_suite(suite) -> [];
 
45
init_per_suite(doc) -> [];
 
46
init_per_suite(Config) when is_list(Config) ->
 
47
    case is_app(asn1) of
 
48
        {ok, AppFile} ->
 
49
            io:format("AppFile: ~n~p~n", [AppFile]),
 
50
            [{app_file, AppFile}|Config];
 
51
        {error, Reason} ->
 
52
            fail(Reason)
 
53
    end.
 
54
 
 
55
is_app(App) ->
 
56
    LibDir = code:lib_dir(App),
 
57
    File = filename:join([LibDir, "ebin", atom_to_list(App) ++ ".app"]),
 
58
    case file:consult(File) of
 
59
        {ok, [{application, App, AppFile}]} ->
 
60
            {ok, AppFile};
 
61
        Error ->
 
62
            {error, {invalid_format, Error}}
 
63
    end.
 
64
 
 
65
 
 
66
end_per_suite(suite) -> [];
 
67
end_per_suite(doc) -> [];
 
68
end_per_suite(Config) when is_list(Config) ->
 
69
    Config.
 
70
 
 
71
 
 
72
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
73
 
 
74
fields(suite) ->
 
75
    [];
 
76
fields(doc) ->
 
77
    [];
 
78
fields(Config) when is_list(Config) ->
 
79
    AppFile = key1search(app_file, Config),
 
80
    Fields = [vsn, description, modules, registered, applications],
 
81
    case check_fields(Fields, AppFile, []) of
 
82
        [] ->
 
83
            ok;
 
84
        Missing ->
 
85
            fail({missing_fields, Missing})
 
86
    end.
 
87
 
 
88
check_fields([], _AppFile, Missing) ->
 
89
    Missing;
 
90
check_fields([Field|Fields], AppFile, Missing) ->
 
91
    check_fields(Fields, AppFile, check_field(Field, AppFile, Missing)).
 
92
 
 
93
check_field(Name, AppFile, Missing) ->
 
94
    io:format("checking field: ~p~n", [Name]),
 
95
    case lists:keymember(Name, 1, AppFile) of
 
96
        true ->
 
97
            Missing;
 
98
        false ->
 
99
            [Name|Missing]
 
100
    end.
 
101
 
 
102
 
 
103
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
104
 
 
105
modules(suite) ->
 
106
    [];
 
107
modules(doc) ->
 
108
    [];
 
109
modules(Config) when is_list(Config) ->
 
110
    AppFile  = key1search(app_file, Config),
 
111
    Mods     = key1search(modules, AppFile),
 
112
    EbinList = get_ebin_mods(asn1),
 
113
    case missing_modules(Mods, EbinList, []) of
 
114
        [] ->
 
115
            ok;
 
116
        Missing ->
 
117
            throw({error, {missing_modules, Missing}})
 
118
    end,
 
119
    case extra_modules(Mods, EbinList, []) of
 
120
        [] ->
 
121
            ok;
 
122
        Extra ->
 
123
            check_asn1ct_modules(Extra)
 
124
%           throw({error, {extra_modules, Extra}})
 
125
    end,
 
126
    {ok, Mods}.
 
127
            
 
128
get_ebin_mods(App) ->
 
129
    LibDir  = code:lib_dir(App),
 
130
    EbinDir = filename:join([LibDir,"ebin"]),
 
131
    {ok, Files0} = file:list_dir(EbinDir),
 
132
    Files1 = [lists:reverse(File) || File <- Files0],
 
133
    [list_to_atom(lists:reverse(Name)) || [$m,$a,$e,$b,$.|Name] <- Files1].
 
134
 
 
135
check_asn1ct_modules(Extra) ->
 
136
    ASN1CTMods = [asn1ct,asn1ct_check,asn1_db,asn1ct_pretty_format,
 
137
                  asn1ct_gen,asn1ct_gen_per,asn1ct_gen_per_rt2ct,
 
138
                  asn1ct_name,asn1ct_constructed_per,asn1ct_constructed_ber,
 
139
                  asn1ct_gen_ber,asn1ct_constructed_ber_bin_v2,
 
140
                  asn1ct_gen_ber_bin_v2,asn1ct_value,
 
141
                  asn1ct_tok,asn1ct_parser2],
 
142
    case Extra -- ASN1CTMods of
 
143
        [] ->
 
144
            ok;
 
145
        Extra2 ->
 
146
            throw({error, {extra_modules, Extra2}})
 
147
    end.
 
148
 
 
149
missing_modules([], _Ebins, Missing) ->
 
150
    Missing;
 
151
missing_modules([Mod|Mods], Ebins, Missing) ->
 
152
    case lists:member(Mod, Ebins) of
 
153
        true ->
 
154
            missing_modules(Mods, Ebins, Missing);
 
155
        false ->
 
156
            io:format("missing module: ~p~n", [Mod]),
 
157
            missing_modules(Mods, Ebins, [Mod|Missing])
 
158
    end.
 
159
 
 
160
 
 
161
extra_modules(_Mods, [], Extra) ->
 
162
    Extra;
 
163
extra_modules(Mods, [Mod|Ebins], Extra) ->
 
164
    case lists:member(Mod, Mods) of
 
165
        true ->
 
166
            extra_modules(Mods, Ebins, Extra);
 
167
        false ->
 
168
            io:format("supefluous module: ~p~n", [Mod]),
 
169
            extra_modules(Mods, Ebins, [Mod|Extra])
 
170
    end.
 
171
 
 
172
 
 
173
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
174
 
 
175
 
 
176
exportall(suite) ->
 
177
    [];
 
178
exportall(doc) ->
 
179
    [];
 
180
exportall(Config) when is_list(Config) ->
 
181
    AppFile = key1search(app_file, Config),
 
182
    Mods    = key1search(modules, AppFile),
 
183
    check_export_all(Mods).
 
184
 
 
185
 
 
186
check_export_all([]) ->
 
187
    ok;
 
188
check_export_all([Mod|Mods]) ->
 
189
    case (catch apply(Mod, module_info, [compile])) of
 
190
        {'EXIT', {undef, _}} ->
 
191
            check_export_all(Mods);
 
192
        O ->
 
193
            case lists:keysearch(options, 1, O) of
 
194
                false ->
 
195
                    check_export_all(Mods);
 
196
                {value, {options, List}} ->
 
197
                    case lists:member(export_all, List) of
 
198
                        true ->
 
199
                            throw({error, {export_all, Mod}});
 
200
                        false ->
 
201
                            check_export_all(Mods)
 
202
                    end
 
203
            end
 
204
    end.
 
205
 
 
206
            
 
207
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
208
 
 
209
app_depend(suite) ->
 
210
    [];
 
211
app_depend(doc) ->
 
212
    [];
 
213
app_depend(Config) when is_list(Config) ->
 
214
    AppFile = key1search(app_file, Config),
 
215
    Apps    = key1search(applications, AppFile),
 
216
    check_apps(Apps).
 
217
 
 
218
 
 
219
check_apps([]) ->
 
220
    ok;
 
221
check_apps([App|Apps]) ->
 
222
    case is_app(App) of
 
223
        {ok, _} ->
 
224
            check_apps(Apps);
 
225
        Error ->
 
226
            throw({error, {missing_app, {App, Error}}})
 
227
    end.
 
228
 
 
229
 
 
230
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
231
 
 
232
 
 
233
fail(Reason) ->
 
234
    exit({suite_failed, Reason}).
 
235
 
 
236
key1search(Key, L) ->
 
237
    case lists:keysearch(Key, 1, L) of
 
238
        undefined ->
 
239
            fail({not_found, Key, L});
 
240
        {value, {Key, Value}} ->
 
241
            Value
 
242
    end.