~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/tools/test/cprof_SUITE.erl

  • Committer: Elliot Murphy
  • Date: 2010-06-08 03:55:44 UTC
  • mfrom: (3.5.6 squeeze)
  • Revision ID: elliot@elliotmurphy.com-20100608035544-dd8zh2swk7jr5rz2
* Merge with Debian unstable; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Added missing symlinks to /usr/include for a few new header files.
* Fixed generation of ${erlang-base:Depends} and ${erlang-x11:Depends}
  substitution variables.
* Added a fix for a re:compile/2 crash on a long regular expression.
* Changed urgency to medium as the change fixes a security bug.
* Manpages in section 1 are needed even if only arch-dependent packages are
  built. So, re-enabled them.
* Fixed HiPE architecture recognition for powerpc Debian architecture.
* Moved xsltproc and fop to build-depends-indep and do not build
  documentation if only architecture-specific packages are built.
* Refreshed all patches.
* Made Emacs look in man5 and man7 for Erlang manpages and added code
  skeleton files to erlang-mode package.
* New upstream release.
* Moved manpages from incorrect sections 4 and 6 to correct 5 and 7
  (closes: #498492).
* Made manpages regexp in Emacs mode match only 3erl pages in section 3.
* Removed docb_gen script which is no longer needed to build manpages.
* Added erlang-doc package which contains documentation in HTML and PDF
  formats. This package replaces erlang-doc-html package and it's easier
  to synchronize it with the main Erlang packages as it's built from
  a single source package (closes: #558451).
* Removed RPATH from ssl and crypto application binaries as required by
  Debian policy.
* Added libwxgtk2.4-dev and libwxgtk2.6-dev to build conflicts.
* Added a few dpendencies for erlang-dialyzer, erlang-et, erlang-observer
  and erlang-examples packages which now call functions from more modules
  than in 1:13.b.3.
* Added a workaround which disables vfork() for hppa architecture
  (closes: #562218).
* Strictened check for JDK 1.5 adding a call to String(int[], int, int)
  because GCJ 4.4 doesn't implement it and OpenJDK isn't available for all
  architectures.
* Fixed erlang-manpages package section.
* Made erlang-depends add only substvars which are requested in
  debian/control file. This minimizes number of warnings from dh_gencontrol.
  Also, improved descriptions of the functions in erlang-depends escript.
* Added erlang-erl-docgen package to erlang-nox dependencies.
* Made dummy packages erlang-nox and erlang-x11 architecture all.
* Cleaned up working with custom substitution variables in debian/rules.
* Reorganized debian/rules to ensure that manpages arent built twice, and
  aren't built at all if only architecture-dependent packages are requested.
* Fixed project links in README.Debian.
* Added a new package erlang-jinterface which provides tools for
  communication of Java programs with Erlang processes. This adds build
  depandency on default-jdk and as a result enables Java module for IDL
  compiler.
* Bumped standards version to 3.8.4.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2002-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
%%%
 
22
%%% Define to run outside of test server
 
23
%%%
 
24
%%% -define(STANDALONE,1).
 
25
%%%
 
26
%%%
 
27
%%% Define for debug output
 
28
%%%
 
29
%%% -define(debug,1).
 
30
 
 
31
-module(cprof_SUITE).
 
32
 
 
33
%% Exported end user tests
 
34
-export([basic_test/0, on_load_test/1, modules_test/1]).
 
35
 
 
36
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
37
%% Test server related stuff
 
38
%%
 
39
 
 
40
-ifdef(STANDALONE).
 
41
-define(config(A,B),config(A,B)).
 
42
-export([config/2]).
 
43
-else.
 
44
-include("test_server.hrl").
 
45
-endif.
 
46
 
 
47
-ifdef(debug).
 
48
-ifdef(STANDALONE).
 
49
-define(line, erlang:display({?MODULE,?LINE}), ).
 
50
-endif.
 
51
-define(dbgformat(A,B),io:format(A,B)).
 
52
-else.
 
53
-ifdef(STANDALONE).
 
54
-define(line, noop, ).
 
55
-endif.
 
56
-define(dbgformat(A,B),noop).
 
57
-endif.
 
58
 
 
59
-ifdef(STANDALONE).
 
60
config(priv_dir, _) ->
 
61
    ".";
 
62
config(data_dir, _) ->
 
63
    "cprof_SUITE_data".
 
64
-else.
 
65
%% When run in test server.
 
66
-export([all/1, init_per_testcase/2, fin_per_testcase/2, not_run/1]).
 
67
-export([basic/1, on_load/1, modules/1]).
 
68
         
 
69
init_per_testcase(_Case, Config) ->
 
70
    ?line Dog=test_server:timetrap(test_server:seconds(30)),
 
71
    [{watchdog, Dog}|Config].
 
72
 
 
73
fin_per_testcase(_Case, Config) ->
 
74
    erlang:trace_pattern({'_','_','_'}, false, [local,meta,call_count]),
 
75
    erlang:trace_pattern(on_load, false, [local,meta,call_count]),
 
76
    erlang:trace(all, false, [all]),
 
77
    Dog=?config(watchdog, Config),
 
78
    test_server:timetrap_cancel(Dog),
 
79
    ok.
 
80
 
 
81
all(doc) ->
 
82
    ["Test the cprof profiling tool."];
 
83
all(suite) ->
 
84
    case test_server:is_native(?MODULE) of
 
85
        true -> [not_run];
 
86
        false -> [basic, on_load, modules]
 
87
%, on_and_off, info, 
 
88
%                 pause_and_restart, combo]
 
89
    end.
 
90
 
 
91
not_run(Config) when is_list(Config) -> 
 
92
    {skipped,"Native code"}.
 
93
 
 
94
basic(suite) ->
 
95
    [];
 
96
basic(doc) ->
 
97
    ["Tests basic profiling"];
 
98
basic(Config) when is_list(Config) ->
 
99
    basic_test().
 
100
 
 
101
on_load(suite) ->
 
102
    [];
 
103
on_load(doc) ->
 
104
    ["Tests profiling of unloaded module"];
 
105
on_load(Config) when is_list(Config) ->
 
106
    on_load_test(Config).
 
107
 
 
108
modules(suite) ->
 
109
    [];
 
110
modules(doc) ->
 
111
    ["Tests profiling of several modules"];
 
112
modules(Config) when is_list(Config) ->
 
113
    modules_test(Config).
 
114
 
 
115
-endif. %-ifdef(STANDALONE). ... -else.
 
116
 
 
117
%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
118
%%% The Tests
 
119
%%%
 
120
 
 
121
basic_test() ->
 
122
    ?line M = 1000,
 
123
    %%
 
124
    ?line M2 = M*2,
 
125
    ?line M3 = M*3,
 
126
    ?line M2__1 = M2 + 1,
 
127
    ?line M3__1 = M3 + 1,
 
128
    ?line N = cprof:stop(),
 
129
    %%
 
130
    ?line 2 = cprof:start(?MODULE, seq_r),
 
131
    ?line 1 = cprof:start(?MODULE, seq, 3),
 
132
    ?line L = seq(1, M, fun succ/1),
 
133
    ?line Lr = seq_r(1, M, fun succ/1),
 
134
    ?line L = lists:reverse(Lr),
 
135
    %%
 
136
    ?line io:format("~p~n~p~n~p~n", 
 
137
                    [erlang:trace_info({?MODULE,sec_r,3}, all),
 
138
                     erlang:trace_info({?MODULE,sec_r,4}, all),
 
139
                     erlang:trace_info({?MODULE,sec,3}, all)]),
 
140
    %%
 
141
    ?line ModAna1 = {?MODULE,M2__1,[{{?MODULE,seq_r,4},M},
 
142
                                   {{?MODULE,seq,3},M},
 
143
                                   {{?MODULE,seq_r,3},1}]},
 
144
    ?line ModAna1 = cprof:analyse(?MODULE,0),
 
145
    ?line {M2__1, [ModAna1]} = cprof:analyse(),
 
146
    ?line ModAna1 = cprof:analyse(?MODULE, 1),
 
147
    ?line {M2__1, [ModAna1]} = cprof:analyse(1),
 
148
    %%
 
149
    ?line ModAna2 = {?MODULE,M2__1,[{{?MODULE,seq_r,4},M},
 
150
                                   {{?MODULE,seq,3},M}]},
 
151
    ?line ModAna2 = cprof:analyse(?MODULE, 2),
 
152
    ?line {M2__1, [ModAna2]} = cprof:analyse(2),
 
153
    %%
 
154
    2 = cprof:pause(?MODULE, seq_r),
 
155
    ?line L = seq(1, M, fun succ/1),
 
156
    ?line Lr = seq_r(1, M, fun succ/1),
 
157
    %%
 
158
    ?line ModAna3 = {?MODULE,M3__1,[{{?MODULE,seq,3},M2},
 
159
                                   {{?MODULE,seq_r,4},M},
 
160
                                   {{?MODULE,seq_r,3},1}]},
 
161
    ?line ModAna3 = cprof:analyse(?MODULE),
 
162
    %%
 
163
    ?line N = cprof:pause(),
 
164
    ?line L = seq(1, M, fun succ/1),
 
165
    ?line Lr = seq_r(1, M, fun succ/1),
 
166
    %%
 
167
    ?line {M3__1, [ModAna3]} = cprof:analyse(),
 
168
    %%
 
169
    ?line N = cprof:restart(),
 
170
    ?line L = seq(1, M, fun succ/1),
 
171
    ?line Lr = seq_r(1, M, fun succ/1),
 
172
    %%
 
173
    ?line ModAna1 = cprof:analyse(?MODULE),
 
174
    %%
 
175
    ?line N = cprof:stop(),
 
176
    ?line {?MODULE,0,[]} = cprof:analyse(?MODULE),
 
177
    ?line {0,[]} = cprof:analyse(),
 
178
    ok.
 
179
 
 
180
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
181
 
 
182
on_load_test(Config) ->
 
183
    ?line Priv = ?config(priv_dir, Config),
 
184
    ?line Data = ?config(data_dir, Config),
 
185
    ?line File = filename:join(Data, "cprof_SUITE_test"),
 
186
    ?line Module = cprof_SUITE_test,
 
187
    ?line M = 1000,
 
188
    %%
 
189
    ?line M2 = M*2,
 
190
    ?line M2__1 = M2 + 1,
 
191
    ?line N1 = cprof:start(),
 
192
 
 
193
    ?line {ok,Module} = c:c(File, [{outdir,Priv}]),
 
194
 
 
195
    %% If this system is hipe-enabled, the loader may have called module_info/1
 
196
    %% when Module was loaded above. Reset the call count to avoid seeing
 
197
    %% the call in the analysis below.
 
198
 
 
199
    ?line 1 = cprof:restart(Module, module_info, 1),
 
200
 
 
201
    ?line L = Module:seq(1, M, fun succ/1),
 
202
    ?line Lr = Module:seq_r(1, M, fun succ/1),
 
203
    ?line Lr = lists:reverse(L),
 
204
    ?line N2 = cprof:pause(),
 
205
    ?line N3 = cprof:pause(Module),
 
206
    ?line {Module,M2__1,[{{Module,seq_r,4},M},
 
207
                         {{Module,seq,3},M},
 
208
                         {{Module,seq_r,3},1}]} = cprof:analyse(Module),
 
209
    ?line io:format("~p ~p ~p~n", [N1, N2, N3]),
 
210
    ?line code:purge(Module),
 
211
    ?line code:delete(Module),
 
212
    ?line N4 = N2 - N3,
 
213
    %%
 
214
    ?line N4 = cprof:restart(),
 
215
    ?line {ok,Module} = c:c(File, [{outdir,Priv}]),
 
216
    ?line L = Module:seq(1, M, fun succ/1),
 
217
    ?line Lr = Module:seq_r(1, M, fun succ/1),
 
218
    ?line L = seq(1, M, fun succ/1),
 
219
    ?line Lr = seq_r(1, M, fun succ/1),
 
220
    ?line N2 = cprof:pause(),
 
221
    ?line {Module,0,[]} = cprof:analyse(Module),
 
222
    ?line M_1 = M - 1,
 
223
    ?line M4__4 = M*4 - 4,
 
224
    ?line M10_7 = M*10 - 7,
 
225
    ?line {?MODULE,M10_7,[{{?MODULE,succ,1},M4__4},
 
226
                          {{?MODULE,seq_r,4},M},
 
227
                          {{?MODULE,seq,3},M},
 
228
                          {{?MODULE,'-on_load_test/1-fun-5-',1},M_1},
 
229
                          {{?MODULE,'-on_load_test/1-fun-4-',1},M_1},
 
230
                          {{?MODULE,'-on_load_test/1-fun-3-',1},M_1},
 
231
                          {{?MODULE,'-on_load_test/1-fun-2-',1},M_1},
 
232
                          {{?MODULE,seq_r,3},1}]} 
 
233
        = cprof:analyse(?MODULE),
 
234
    ?line N2 = cprof:stop(),
 
235
    ok.
 
236
 
 
237
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
238
 
 
239
modules_test(Config) ->
 
240
    ?line Priv = ?config(priv_dir, Config),
 
241
    ?line Data = ?config(data_dir, Config),
 
242
    ?line File = filename:join(Data, "cprof_SUITE_test"),
 
243
    ?line Module = cprof_SUITE_test,
 
244
    ?line {ok,Module} = c:c(File, [{outdir,Priv}]),
 
245
    ?line M = 10,
 
246
    %%
 
247
    ?line M2 = M*2,
 
248
    ?line M2__1 = M2 + 1,
 
249
    ?line erlang:yield(),
 
250
    ?line N = cprof:start(),
 
251
    ?line L = Module:seq(1, M, fun succ/1),
 
252
    ?line Lr = Module:seq_r(1, M, fun succ/1),
 
253
    ?line L = seq(1, M, fun succ/1),
 
254
    ?line Lr = seq_r(1, M, fun succ/1),
 
255
    ?line N = cprof:pause(),
 
256
    ?line Lr = lists:reverse(L),
 
257
    ?line M_1 = M - 1,
 
258
    ?line M4_4 = M*4 - 4,
 
259
    ?line M10_7 = M*10 - 7,
 
260
    ?line M2__1 = M*2 + 1,
 
261
    ?line {Tot,ModList} = cprof:analyse(),
 
262
    ?line {value,{?MODULE,M10_7,[{{?MODULE,succ,1},M4_4},
 
263
                                 {{?MODULE,seq_r,4},M},
 
264
                                 {{?MODULE,seq,3},M},
 
265
                                 {{?MODULE,'-modules_test/1-fun-3-',1},M_1},
 
266
                                 {{?MODULE,'-modules_test/1-fun-2-',1},M_1},
 
267
                                 {{?MODULE,'-modules_test/1-fun-1-',1},M_1},
 
268
                                 {{?MODULE,'-modules_test/1-fun-0-',1},M_1},
 
269
                                 {{?MODULE,seq_r,3},1}]}} =
 
270
        lists:keysearch(?MODULE, 1, ModList),
 
271
    ?line {value,{Module,M2__1,[{{Module,seq_r,4},M},
 
272
                                {{Module,seq,3},M},
 
273
                                {{Module,seq_r,3},1}]}} = 
 
274
        lists:keysearch(Module, 1, ModList),
 
275
    ?line Tot = lists:foldl(fun ({_,C,_}, A) -> C+A end, 0, ModList),
 
276
    ?line {cprof,_,Prof} = cprof:analyse(cprof),
 
277
    ?line {value,{{cprof,pause,0},1}} = 
 
278
        lists:keysearch({cprof,pause,0}, 1, Prof),
 
279
    ?line N = cprof:stop(),
 
280
    ok.
 
281
 
 
282
 
 
283
 
 
284
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
285
%% Local helpers
 
286
 
 
287
 
 
288
 
 
289
%% Stack recursive seq
 
290
seq(Stop, Stop, Succ) when is_function(Succ) ->
 
291
    [Stop];
 
292
seq(Start, Stop, Succ) when is_function(Succ) ->
 
293
    [Start | seq(Succ(Start), Stop, Succ)].
 
294
 
 
295
 
 
296
 
 
297
%% Tail recursive seq, result list is reversed
 
298
seq_r(Start, Stop, Succ) when is_function(Succ) ->
 
299
    seq_r(Start, Stop, Succ, []).
 
300
 
 
301
seq_r(Stop, Stop, _, R) ->
 
302
    [Stop | R];
 
303
seq_r(Start, Stop, Succ, R) ->
 
304
    seq_r(Succ(Start), Stop, Succ, [Start | R]).
 
305
 
 
306
 
 
307
 
 
308
%% Successor
 
309
succ(X) -> X+1.