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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_cost.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 1996-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(mnesia_cost).
 
22
-compile(export_all).
 
23
 
 
24
%% This code exercises the mnesia system and produces a bunch
 
25
%% of measurements on what various things cost
 
26
 
 
27
-define(TIMES, 1000).  %% set to at least 1000 when running for real !!
 
28
 
 
29
%% This is the record we perform all ops on in this test
 
30
 
 
31
-record(item, {a = 1234,
 
32
               b = foobar,
 
33
               c = "1.2.3.4",
 
34
               d = {'Lennart', 'Hyland'},
 
35
               e = true 
 
36
              }).
 
37
 
 
38
go() ->
 
39
    go([node() | nodes()]).
 
40
    
 
41
go(Nodes) when hd(Nodes) == node() ->
 
42
    {ok, Out} = file:open("MNESIA_COST", write),
 
43
    put(out, Out),
 
44
    
 
45
    rpc:multicall(Nodes, mnesia, lkill, []),
 
46
    ok = mnesia:delete_schema(Nodes),
 
47
    ok = mnesia:create_schema(Nodes),
 
48
    rpc:multicall(Nodes, mnesia, start, []),
 
49
    TabDef = [{attributes, record_info(fields, item)}],
 
50
    {atomic, ok} = mnesia:create_table(item, TabDef),
 
51
 
 
52
    round("single ram copy", "no index"),
 
53
    {atomic, ok} = mnesia:add_table_index(item, #item.e),
 
54
    round("single ram copy", "One index"),
 
55
 
 
56
    {atomic, ok} = mnesia:add_table_index(item, #item.c),
 
57
    round("single ram copy", "Two indexes"),
 
58
 
 
59
    {atomic, ok} = mnesia:del_table_index(item, #item.e),
 
60
    {atomic, ok} = mnesia:del_table_index(item, #item.c),
 
61
 
 
62
    {atomic, ok} = mnesia:change_table_copy_type(item, node(), disc_copies),
 
63
    round("single disc copy", "no index"),
 
64
 
 
65
    {atomic, ok} = mnesia:change_table_copy_type(item, node(), ram_copies),
 
66
 
 
67
    case length(Nodes) of
 
68
        Len when Len < 2 ->
 
69
            format("<WARNING> replication skipped. Too few nodes.", []);
 
70
        _Len ->
 
71
            N2 = lists:nth(2, Nodes),
 
72
            {atomic, ok} = mnesia:add_table_copy(item, N2, ram_copies),
 
73
            round("2 replicated ram copy", "no index")
 
74
    end,
 
75
    file:close(Out),
 
76
    erase(out),
 
77
    ok.
 
78
 
 
79
round(Replication, Index) ->
 
80
    run(Replication, Index, [write],
 
81
        fun() -> mnesia:write(#item{}) end),
 
82
 
 
83
 
 
84
    run(Replication, Index, [read],
 
85
        fun() -> mnesia:read({item, 1234}) end),
 
86
 
 
87
    run(Replication, Index, [read, write],
 
88
        fun() -> mnesia:read({item, 1234}),
 
89
                 mnesia:write(#item{}) end),
 
90
 
 
91
    run(Replication, Index, [wread, write],
 
92
        fun() -> mnesia:wread({item, 1234}),
 
93
                 mnesia:write(#item{}) end),
 
94
 
 
95
 
 
96
    run(Replication, Index, [match, write, write, write],
 
97
        fun() -> mnesia:match_object({item, 1, '_', '_', '_', true}),
 
98
                 mnesia:write(#item{a =1}),
 
99
                 mnesia:write(#item{a =2}),
 
100
                 mnesia:write(#item{a =3}) end).
 
101
 
 
102
 
 
103
format(F, As) ->
 
104
    io:format(get(out), F, As).
 
105
 
 
106
run(What, OtherInfo, Ops, F) ->
 
107
    run(t, What, OtherInfo, Ops, F).
 
108
 
 
109
run(How, What, OtherInfo, Ops, F) ->
 
110
    T1 = erlang:now(),
 
111
    statistics(runtime),
 
112
    do_times(How, ?TIMES, F),
 
113
    {_, RunTime} = statistics(runtime),
 
114
    T2 = erlang:now(),
 
115
    RealTime = subtr(T1, T2),
 
116
    report(How, What, OtherInfo, Ops, RunTime, RealTime).
 
117
 
 
118
report(t, What, OtherInfo, Ops, RunTime, RealTime) ->
 
119
    format("~s, ~s,  transaction call ", [What, OtherInfo]),
 
120
    format("Ops is ", []),
 
121
    lists:foreach(fun(Op) -> format("~w-", [Op]) end, Ops),
 
122
 
 
123
    format("~n   ~w/~w Millisecs/Trans ~w/~w MilliSecs/Operation ~n~n",
 
124
              [RunTime/?TIMES, 
 
125
               RealTime/?TIMES,
 
126
               RunTime/(?TIMES*length(Ops)),
 
127
               RealTime/(?TIMES*length(Ops))]);
 
128
 
 
129
report(dirty, What, OtherInfo, Ops, RunTime, RealTime) ->
 
130
    format("~s, ~s, dirty calls ", [What, OtherInfo]),
 
131
    format("Ops is ", []),
 
132
    lists:foreach(fun(Op) -> format("~w-", [Op]) end, Ops),
 
133
 
 
134
    format("~n   ~w/~w Millisecs/Bunch ~w/~w MilliSecs/Operation ~n~n",
 
135
              [RunTime/?TIMES, 
 
136
               RealTime/?TIMES,
 
137
               RunTime/(?TIMES*length(Ops)),
 
138
               RealTime/(?TIMES*length(Ops))]).
 
139
 
 
140
 
 
141
subtr(Before, After) ->
 
142
    E =(element(1,After)*1000000000000
 
143
        +element(2,After)*1000000+element(3,After)) -
 
144
        (element(1,Before)*1000000000000
 
145
         +element(2,Before)*1000000+element(3,Before)),
 
146
    E div 1000.
 
147
 
 
148
do_times(t, I, F) ->
 
149
    do_trans_times(I, F);
 
150
do_times(dirty, I, F) ->
 
151
    do_dirty(I, F).
 
152
 
 
153
do_trans_times(I, F) when I /= 0 ->
 
154
    {atomic, _} = mnesia:transaction(F),
 
155
    do_trans_times(I-1, F);
 
156
do_trans_times(_,_) -> ok.
 
157
 
 
158
do_dirty(I, F) when I /= 0 ->
 
159
    F(),
 
160
    do_dirty(I-1, F);
 
161
do_dirty(_,_) -> ok.
 
162
 
 
163
    
 
164
    
 
165
table_load([N1,N2| _ ] = Ns) ->    
 
166
    Nodes = [N1,N2],
 
167
    rpc:multicall(Ns, mnesia, lkill, []),
 
168
    ok = mnesia:delete_schema(Ns),
 
169
    ok = mnesia:create_schema(Nodes),
 
170
    rpc:multicall(Nodes, mnesia, start, []),
 
171
    TabDef = [{disc_copies,[N1]},{ram_copies,[N2]},
 
172
              {attributes,record_info(fields,item)},{record_name,item}],
 
173
    Tabs   = [list_to_atom("tab" ++ integer_to_list(I)) || I <- lists:seq(1,400)],
 
174
    
 
175
    [mnesia:create_table(Tab,TabDef) || Tab <- Tabs],
 
176
 
 
177
%%     InitTab = fun(Tab) ->
 
178
%%                    mnesia:write_lock_table(Tab),
 
179
%%                    InitRec = fun(Key) -> mnesia:write(Tab,#item{a=Key},write) end,
 
180
%%                    lists:foreach(InitRec, lists:seq(1,100))
 
181
%%            end,
 
182
%%     
 
183
%%    {Time,{atomic,ok}} = timer:tc(mnesia,transaction, [fun() ->lists:foreach(InitTab, Tabs) end]),
 
184
    mnesia:dump_log(),
 
185
%%    io:format("Init took ~p msec ~n", [Time/1000]),
 
186
    rpc:call(N2, mnesia, stop, []),    timer:sleep(1000),
 
187
    mnesia:stop(), timer:sleep(500),
 
188
    %% Warmup
 
189
    ok = mnesia:start([{no_table_loaders, 1}]),    
 
190
    timer:tc(mnesia, wait_for_tables, [Tabs, infinity]),
 
191
    mnesia:dump_log(),
 
192
    rpc:call(N2, mnesia, dump_log, []),
 
193
    io:format("Initialized ~n",[]),
 
194
 
 
195
    mnesia:stop(), timer:sleep(1000),
 
196
    ok = mnesia:start([{no_table_loaders, 1}]),
 
197
    {T1, ok} = timer:tc(mnesia, wait_for_tables, [Tabs, infinity]),
 
198
    io:format("Loading from disc with 1 loader ~p msec~n",[T1/1000]),
 
199
    mnesia:stop(), timer:sleep(1000),
 
200
    ok = mnesia:start([{no_table_loaders, 4}]),
 
201
    {T2, ok} = timer:tc(mnesia, wait_for_tables, [Tabs, infinity]),
 
202
    io:format("Loading from disc with 4 loader ~p msec~n",[T2/1000]),
 
203
 
 
204
    %% Warmup
 
205
    rpc:call(N2, ?MODULE, remote_load, [Tabs,4]),
 
206
    io:format("Initialized ~n",[]),
 
207
 
 
208
    
 
209
    T3 = rpc:call(N2, ?MODULE, remote_load, [Tabs,1]),
 
210
    io:format("Loading from net with 1 loader ~p msec~n",[T3/1000]),
 
211
    
 
212
    T4 = rpc:call(N2, ?MODULE, remote_load, [Tabs,4]),
 
213
    io:format("Loading from net with 4 loader ~p msec~n",[T4/1000]),
 
214
 
 
215
    ok.
 
216
 
 
217
remote_load(Tabs,Loaders) ->
 
218
    ok = mnesia:start([{no_table_loaders, Loaders}]),
 
219
%%    io:format("~p ~n", [mnesia_controller:get_info(500)]),
 
220
    {Time, ok} = timer:tc(mnesia, wait_for_tables, [Tabs, infinity]),
 
221
    timer:sleep(1000), mnesia:stop(), timer:sleep(1000),
 
222
    Time.