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

« back to all changes in this revision

Viewing changes to erts/emulator/test/mtx_SUITE.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 2010-2011. 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
%% Stress tests of rwmutex implementation.
 
22
%%
 
23
%% Author: Rickard Green
 
24
%%
 
25
-module(mtx_SUITE).
 
26
 
 
27
%%-define(line_trace,true).
 
28
 
 
29
-include_lib("common_test/include/ct.hrl").
 
30
 
 
31
-export([all/0,suite/0,groups/0,
 
32
         init_per_group/2,end_per_group/2, init_per_suite/1, 
 
33
         end_per_suite/1, init_per_testcase/2, end_per_testcase/2]).
 
34
 
 
35
-export([long_rwlock/1,
 
36
         hammer_ets_rwlock/1,
 
37
         hammer_rwlock/1,
 
38
         hammer_rwlock_check/1,
 
39
         hammer_tryrwlock/1,
 
40
         hammer_tryrwlock_check/1,
 
41
         hammer_sched_long_rwlock/1,
 
42
         hammer_sched_long_rwlock_check/1,
 
43
         hammer_sched_long_freqread_rwlock/1,
 
44
         hammer_sched_long_freqread_rwlock_check/1,
 
45
         hammer_sched_long_tryrwlock/1,
 
46
         hammer_sched_long_tryrwlock_check/1,
 
47
         hammer_sched_long_freqread_tryrwlock/1,
 
48
         hammer_sched_long_freqread_tryrwlock_check/1,
 
49
         hammer_sched_rwlock/1,
 
50
         hammer_sched_rwlock_check/1,
 
51
         hammer_sched_freqread_rwlock/1,
 
52
         hammer_sched_freqread_rwlock_check/1,
 
53
         hammer_sched_tryrwlock/1,
 
54
         hammer_sched_tryrwlock_check/1,
 
55
         hammer_sched_freqread_tryrwlock/1,
 
56
         hammer_sched_freqread_tryrwlock_check/1]).
 
57
 
 
58
init_per_suite(Config) when is_list(Config) ->
 
59
    DataDir = ?config(data_dir, Config),
 
60
    Lib = filename:join([DataDir, atom_to_list(?MODULE)]),
 
61
    ok = erlang:load_nif(Lib, none),
 
62
    Config.
 
63
 
 
64
end_per_suite(Config) when is_list(Config) ->
 
65
    Config.
 
66
 
 
67
init_per_testcase(_Case, Config) ->
 
68
    Dog = ?t:timetrap(?t:minutes(15)),
 
69
    [{watchdog, Dog}|Config].
 
70
 
 
71
end_per_testcase(_Func, Config) ->
 
72
    Dog = ?config(watchdog, Config),
 
73
    ?t:timetrap_cancel(Dog).
 
74
 
 
75
suite() -> [{ct_hooks,[ts_install_cth]}].
 
76
 
 
77
all() -> 
 
78
    [long_rwlock, hammer_rwlock_check, hammer_rwlock,
 
79
     hammer_tryrwlock_check, hammer_tryrwlock,
 
80
     hammer_ets_rwlock, hammer_sched_long_rwlock_check,
 
81
     hammer_sched_long_rwlock,
 
82
     hammer_sched_long_freqread_rwlock_check,
 
83
     hammer_sched_long_freqread_rwlock,
 
84
     hammer_sched_long_tryrwlock_check,
 
85
     hammer_sched_long_tryrwlock,
 
86
     hammer_sched_long_freqread_tryrwlock_check,
 
87
     hammer_sched_long_freqread_tryrwlock,
 
88
     hammer_sched_rwlock_check, hammer_sched_rwlock,
 
89
     hammer_sched_freqread_rwlock_check,
 
90
     hammer_sched_freqread_rwlock,
 
91
     hammer_sched_tryrwlock_check, hammer_sched_tryrwlock,
 
92
     hammer_sched_freqread_tryrwlock_check,
 
93
     hammer_sched_freqread_tryrwlock].
 
94
 
 
95
groups() -> 
 
96
    [].
 
97
 
 
98
init_per_group(_GroupName, Config) ->
 
99
        Config.
 
100
 
 
101
end_per_group(_GroupName, Config) ->
 
102
        Config.
 
103
 
 
104
 
 
105
long_rwlock(Config) when is_list(Config) ->
 
106
    statistics(runtime),
 
107
    LLRes = long_rw_test(),
 
108
    {_, RunTime} = statistics(runtime),
 
109
    %% A very short run time is expected, since
 
110
    %% threads in the test mostly wait
 
111
    ?t:format("RunTime=~p~n", [RunTime]),
 
112
    ?line true = RunTime < 100,
 
113
    ?line RunTimeStr = "Run-time during test was "++integer_to_list(RunTime)++" ms.",
 
114
    case LLRes of
 
115
        ok ->
 
116
            {comment, RunTimeStr};
 
117
        {comment, Comment} ->
 
118
            {comment, Comment ++ " " ++ RunTimeStr}
 
119
    end.
 
120
 
 
121
hammer_rwlock(Config) when is_list(Config) ->
 
122
    hammer_rw_test(false).
 
123
 
 
124
hammer_rwlock_check(Config) when is_list(Config) ->
 
125
    hammer_rw_test(true).
 
126
 
 
127
hammer_tryrwlock(Config) when is_list(Config) ->
 
128
    hammer_tryrw_test(false).
 
129
 
 
130
hammer_tryrwlock_check(Config) when is_list(Config) ->
 
131
    hammer_tryrw_test(true).
 
132
 
 
133
hammer_sched_rwlock(Config) when is_list(Config) ->
 
134
    hammer_sched_rwlock_test(false, false, true, 0, 0).
 
135
 
 
136
hammer_sched_rwlock_check(Config) when is_list(Config) ->
 
137
    hammer_sched_rwlock_test(false, true, true, 0, 0).
 
138
 
 
139
hammer_sched_freqread_rwlock(Config) when is_list(Config) ->
 
140
    hammer_sched_rwlock_test(true, false, true, 0, 0).
 
141
 
 
142
hammer_sched_freqread_rwlock_check(Config) when is_list(Config) ->
 
143
    hammer_sched_rwlock_test(true, true, true, 0, 0).
 
144
 
 
145
hammer_sched_tryrwlock(Config) when is_list(Config) ->
 
146
    hammer_sched_rwlock_test(false, false, false, 0, 100).
 
147
 
 
148
hammer_sched_tryrwlock_check(Config) when is_list(Config) ->
 
149
    hammer_sched_rwlock_test(false, true, false, 0, 100).
 
150
 
 
151
hammer_sched_freqread_tryrwlock(Config) when is_list(Config) ->
 
152
    hammer_sched_rwlock_test(true, false, false, 0, 100).
 
153
 
 
154
hammer_sched_freqread_tryrwlock_check(Config) when is_list(Config) ->
 
155
    hammer_sched_rwlock_test(true, true, false, 0, 100).
 
156
 
 
157
hammer_sched_long_rwlock(Config) when is_list(Config) ->
 
158
    hammer_sched_rwlock_test(false, false, true, 100, 0).
 
159
 
 
160
hammer_sched_long_rwlock_check(Config) when is_list(Config) ->
 
161
    hammer_sched_rwlock_test(false, true, true, 100, 0).
 
162
 
 
163
hammer_sched_long_freqread_rwlock(Config) when is_list(Config) ->
 
164
    hammer_sched_rwlock_test(true, false, true, 100, 0).
 
165
 
 
166
hammer_sched_long_freqread_rwlock_check(Config) when is_list(Config) ->
 
167
    hammer_sched_rwlock_test(true, true, true, 100, 0).
 
168
 
 
169
hammer_sched_long_tryrwlock(Config) when is_list(Config) ->
 
170
    hammer_sched_rwlock_test(false, false, false, 100, 100).
 
171
 
 
172
hammer_sched_long_tryrwlock_check(Config) when is_list(Config) ->
 
173
    hammer_sched_rwlock_test(false, true, false, 100, 100).
 
174
 
 
175
hammer_sched_long_freqread_tryrwlock(Config) when is_list(Config) ->
 
176
    hammer_sched_rwlock_test(true, false, false, 100, 100).
 
177
 
 
178
hammer_sched_long_freqread_tryrwlock_check(Config) when is_list(Config) ->
 
179
    hammer_sched_rwlock_test(true, true, false, 100, 100).
 
180
 
 
181
hammer_sched_rwlock_test(FreqRead, LockCheck, Blocking, WaitLocked, WaitUnlocked) ->
 
182
    case create_rwlock(FreqRead, LockCheck) of
 
183
        enotsup ->
 
184
            {skipped, "Not supported."};
 
185
        RWLock ->
 
186
            Onln = erlang:system_info(schedulers_online),
 
187
            NWPs = case Onln div 3 of
 
188
                       1 -> case Onln < 4 of
 
189
                                true -> 1;
 
190
                                false -> 2
 
191
                            end;
 
192
                       X -> X
 
193
                   end,
 
194
            NRPs = Onln - NWPs,
 
195
            NoLockOps = ((((50000000 div Onln)
 
196
                               div case {Blocking, WaitLocked} of
 
197
                                       {false, 0} -> 1;
 
198
                                       _ -> 10
 
199
                                   end)
 
200
                              div (case WaitLocked == 0 of
 
201
                                       true -> 1;
 
202
                                       false -> WaitLocked*250
 
203
                                   end))
 
204
                             div handicap()),
 
205
            ?t:format("NoLockOps=~p~n", [NoLockOps]),
 
206
            Sleep = case Blocking of
 
207
                        true -> NoLockOps;
 
208
                        false -> NoLockOps div 10
 
209
                    end,
 
210
            WPs = lists:map(
 
211
                    fun (Sched) ->
 
212
                            spawn_opt(
 
213
                              fun () ->
 
214
                                      io:format("Writer on scheduler ~p.~n",
 
215
                                                [Sched]),
 
216
                                      Sched = erlang:system_info(scheduler_id),
 
217
                                      receive go -> gone end,
 
218
                                      hammer_sched_rwlock_proc(RWLock,
 
219
                                                               Blocking,
 
220
                                                               true,
 
221
                                                               WaitLocked,
 
222
                                                               WaitUnlocked,
 
223
                                                               NoLockOps,
 
224
                                                               Sleep),
 
225
                                      Sched = erlang:system_info(scheduler_id)
 
226
                              end,
 
227
                              [link, {scheduler, Sched}])
 
228
                    end,
 
229
                    lists:seq(1, NWPs)),
 
230
            RPs = lists:map(
 
231
                    fun (Sched) ->
 
232
                            spawn_opt(
 
233
                              fun () ->
 
234
                                      io:format("Reader on scheduler ~p.~n",
 
235
                                                [Sched]),
 
236
                                      Sched = erlang:system_info(scheduler_id),
 
237
                                      receive go -> gone end,
 
238
                                      hammer_sched_rwlock_proc(RWLock,
 
239
                                                               Blocking,
 
240
                                                               false,
 
241
                                                               WaitLocked,
 
242
                                                               WaitUnlocked,
 
243
                                                               NoLockOps,
 
244
                                                               Sleep),
 
245
                                      Sched = erlang:system_info(scheduler_id)
 
246
                              end,
 
247
                              [link, {scheduler, Sched}])
 
248
                    end,
 
249
                    lists:seq(NWPs + 1, NWPs + NRPs)),
 
250
            Procs = WPs ++ RPs,
 
251
            case {Blocking, WaitLocked} of
 
252
                {_, 0} -> ok;
 
253
                {false, _} -> ok;
 
254
                _ -> statistics(runtime)
 
255
            end,
 
256
            lists:foreach(fun (P) -> P ! go end, Procs),
 
257
            lists:foreach(fun (P) ->
 
258
                                  M = erlang:monitor(process, P),
 
259
                                  receive
 
260
                                      {'DOWN', M, process, P, _} ->
 
261
                                          ok
 
262
                                  end
 
263
                          end,
 
264
                          Procs),
 
265
            case {Blocking, WaitLocked} of
 
266
                {_, 0} -> ok;
 
267
                {false, _} -> ok;
 
268
                _ ->
 
269
                    {_, RunTime} = statistics(runtime),
 
270
                    ?t:format("RunTime=~p~n", [RunTime]),
 
271
                    ?line true = RunTime < 500,
 
272
                    {comment,
 
273
                     "Run-time during test was "
 
274
                     ++ integer_to_list(RunTime)
 
275
                     ++ " ms."}
 
276
            end
 
277
    end.
 
278
 
 
279
hammer_sched_rwlock_proc(_RWLock,
 
280
                         _Blocking,
 
281
                         _WriteOp,
 
282
                         _WaitLocked,
 
283
                         _WaitUnlocked,
 
284
                         0,
 
285
                         _Sleep) ->
 
286
    ok;
 
287
hammer_sched_rwlock_proc(RWLock,
 
288
                         Blocking,
 
289
                         WriteOp,
 
290
                         WaitLocked,
 
291
                         WaitUnlocked,
 
292
                         Times,
 
293
                         Sleep) when Times rem Sleep == 0 ->
 
294
    rwlock_op(RWLock, Blocking, WriteOp, WaitLocked, WaitUnlocked),
 
295
    hammer_sched_rwlock_proc(RWLock,
 
296
                             Blocking,
 
297
                             WriteOp,
 
298
                             WaitLocked,
 
299
                             WaitUnlocked,
 
300
                             Times - 1,
 
301
                             Sleep);
 
302
hammer_sched_rwlock_proc(RWLock,
 
303
                         Blocking,
 
304
                         WriteOp,
 
305
                         WaitLocked,
 
306
                         WaitUnlocked,
 
307
                         Times,
 
308
                         Sleep) ->
 
309
    rwlock_op(RWLock, Blocking, WriteOp, WaitLocked, 0),
 
310
    hammer_sched_rwlock_proc(RWLock,
 
311
                             Blocking,
 
312
                             WriteOp,
 
313
                             WaitLocked,
 
314
                             WaitUnlocked,
 
315
                             Times - 1,
 
316
                             Sleep).
 
317
 
 
318
-define(HAMMER_ETS_RWLOCK_REPEAT_TIMES, 1).
 
319
-define(HAMMER_ETS_RWLOCK_TSIZE, 500).
 
320
 
 
321
hammer_ets_rwlock(Config) when is_list(Config) ->
 
322
    {Ops, Procs} = case handicap() of
 
323
                       1 -> {20000, 500};
 
324
                       2 -> {20000, 50};
 
325
                       3 -> {2000, 50};
 
326
                       _ -> {200, 50}
 
327
                   end,
 
328
    ?t:format("Procs=~p~nOps=~p~n", [Procs, Ops]),
 
329
    lists:foreach(fun (XOpts) ->
 
330
                          ?t:format("Running with extra opts: ~p", [XOpts]),
 
331
                          hammer_ets_rwlock_test(XOpts, true, 2, Ops,
 
332
                                                 Procs, false)
 
333
                  end,
 
334
                  [[],
 
335
                   [{read_concurrency, true}],
 
336
                   [{write_concurrency, true}],
 
337
                   [{read_concurrency, true},{write_concurrency, true}]]),
 
338
    ok.
 
339
 
 
340
%% Aux funcs
 
341
 
 
342
long_rw_test() ->
 
343
    exit(no_nif_implementation).
 
344
 
 
345
hammer_rw_test(_Arg) ->
 
346
    exit(no_nif_implementation).
 
347
 
 
348
hammer_tryrw_test(_Arg) ->
 
349
    exit(no_nif_implementation).
 
350
 
 
351
create_rwlock(_FreqRead, _LockCheck) ->
 
352
    exit(no_nif_implementation).
 
353
 
 
354
rwlock_op(_RWLock, _Blocking, _WriteOp, _WaitLocked, _WaitUnlocked) ->
 
355
    exit(no_nif_implementation).
 
356
 
 
357
hammer_ets_rwlock_put_data() ->
 
358
    put(?MODULE, {"here are some", data, "to store", make_ref()}).
 
359
 
 
360
hammer_ets_rwlock_get_data() ->
 
361
    get(?MODULE).
 
362
 
 
363
hammer_ets_rwlock_ops(_T, _UW, _N, _C, _SC, 0) ->
 
364
    ok;
 
365
hammer_ets_rwlock_ops(T, UW, N, C, SC, Tot) when N >= ?HAMMER_ETS_RWLOCK_TSIZE ->
 
366
    hammer_ets_rwlock_ops(T, UW, 0, C, SC, Tot);
 
367
hammer_ets_rwlock_ops(T, UW, N, 0, SC, Tot) ->
 
368
    case UW of
 
369
        true ->
 
370
            true = ets:insert(T, {N, Tot, hammer_ets_rwlock_get_data()});
 
371
        false ->
 
372
            [{N, _, _}] = ets:lookup(T, N)
 
373
    end,
 
374
    hammer_ets_rwlock_ops(T, UW, N+1, SC, SC, Tot-1);
 
375
hammer_ets_rwlock_ops(T, UW, N, C, SC, Tot) ->
 
376
    case UW of
 
377
        false ->
 
378
            true = ets:insert(T, {N, Tot, hammer_ets_rwlock_get_data()});
 
379
        true ->
 
380
            [{N, _, _}] = ets:lookup(T, N)
 
381
    end,
 
382
    hammer_ets_rwlock_ops(T, UW, N+1, C-1, SC, Tot-1).
 
383
 
 
384
hammer_ets_rwlock_init(T, N) when N < ?HAMMER_ETS_RWLOCK_TSIZE ->
 
385
    ets:insert(T, {N, N, N}),
 
386
    hammer_ets_rwlock_init(T, N+1);
 
387
hammer_ets_rwlock_init(_T, _N) ->
 
388
    ok.
 
389
 
 
390
hammer_ets_rwlock_test(XOpts, UW, C, N, NP, SC) ->
 
391
    receive after 100 -> ok end,
 
392
    {TP, TM} = spawn_monitor(
 
393
                 fun () ->
 
394
                         _L = repeat_list(
 
395
                                fun () ->
 
396
                                        Caller = self(),
 
397
                                        T = fun () ->
 
398
                                                    Parent = self(),
 
399
                                                    hammer_ets_rwlock_put_data(),
 
400
                                                    T=ets:new(x, [public | XOpts]),
 
401
                                                    hammer_ets_rwlock_init(T, 0),
 
402
                                                    Ps0 = repeat_list(
 
403
                                                            fun () ->
 
404
                                                                    spawn_link(
 
405
                                                                      fun () ->
 
406
                                                                              hammer_ets_rwlock_put_data(),
 
407
                                                                              receive go -> ok end,
 
408
                                                                              hammer_ets_rwlock_ops(T, UW, N, C, C, N),
 
409
                                                                              Parent ! {done, self()},
 
410
                                                                              receive after infinity -> ok end
 
411
                                                                      end)
 
412
                                                            end,
 
413
                                                            NP - case SC of
 
414
                                                                     false -> 0;
 
415
                                                                     _ -> 1
 
416
                                                                 end),
 
417
                                                    Ps = case SC of
 
418
                                                             false -> Ps0;
 
419
                                                             _ -> [spawn_link(fun () ->
 
420
                                                                                      hammer_ets_rwlock_put_data(),
 
421
                                                                                      receive go -> ok end,
 
422
                                                                                      hammer_ets_rwlock_ops(T, UW, N, SC, SC, N),
 
423
                                                                                      Parent ! {done, self()},
 
424
                                                                                      receive after infinity -> ok end
 
425
                                                                              end) | Ps0]
 
426
                                                         end,
 
427
                                                    Start = now(),
 
428
                                                    lists:foreach(fun (P) -> P ! go end, Ps),
 
429
                                                    lists:foreach(fun (P) -> receive {done, P} -> ok end end, Ps),
 
430
                                                    Stop = now(),
 
431
                                                    lists:foreach(fun (P) ->
 
432
                                                                          unlink(P),
 
433
                                                                          exit(P, bang),
 
434
                                                                          M = erlang:monitor(process, P),
 
435
                                                                          receive
 
436
                                                                              {'DOWN', M, process, P, _} -> ok
 
437
                                                                          end
 
438
                                                                  end, Ps),
 
439
                                                    Res = timer:now_diff(Stop, Start)/1000000,
 
440
                                                    Caller ! {?MODULE, self(), Res}
 
441
                                            end,
 
442
                                        TP = spawn_link(T),
 
443
                                        receive
 
444
                                            {?MODULE, TP, Res} ->
 
445
                                                Res
 
446
                                        end
 
447
                                end,
 
448
                                ?HAMMER_ETS_RWLOCK_REPEAT_TIMES)
 
449
                 end),
 
450
    receive
 
451
        {'DOWN', TM, process, TP, _} -> ok
 
452
    end.
 
453
 
 
454
repeat_list(Fun, N) ->
 
455
    repeat_list(Fun, N, []).
 
456
 
 
457
repeat_list(_Fun, 0, Acc) ->
 
458
    Acc;
 
459
repeat_list(Fun, N, Acc) ->
 
460
    repeat_list(Fun, N-1, [Fun()|Acc]).
 
461
 
 
462
 
 
463
handicap() ->
 
464
    X0 = case catch (erlang:system_info(logical_processors_available) >=
 
465
                         erlang:system_info(schedulers_online)) of
 
466
             true -> 1;
 
467
             _ -> 2
 
468
         end,
 
469
    case erlang:system_info(build_type) of
 
470
        opt ->
 
471
            X0;
 
472
        ReallySlow when ReallySlow == debug;
 
473
                        ReallySlow == valgrind;
 
474
                        ReallySlow == purify ->
 
475
            X0*3;
 
476
        _Slow ->
 
477
            X0*2
 
478
    end.
 
479