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

« back to all changes in this revision

Viewing changes to lib/et/examples/et_demo.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2002-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2002-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%% 
19
19
%%----------------------------------------------------------------------
23
23
-module(et_demo).
24
24
 
25
25
-export([
26
 
         sim_trans/0,
 
26
         sim_trans/0, sim_trans/1,
 
27
         live_trans/0, live_trans/1,
27
28
         mgr_actors/1,
28
 
         live_trans/0,
29
 
         start/0,
30
 
         start/1,
 
29
         start/0, start/1,
31
30
         filters/0,
32
31
         trace_mnesia/0
33
32
        ]).
34
33
 
 
34
%% Test
 
35
-export([s/0, t/0, t/1, init/0, gen/3]).
 
36
 
35
37
-include_lib("et/include/et.hrl").
36
38
 
37
39
%%----------------------------------------------------------------------
38
40
 
39
41
%sim_trans
40
42
sim_trans() ->
 
43
    sim_trans([]).
 
44
 
 
45
sim_trans(ExtraOptions) ->
41
46
    Options = [{dict_insert, {filter, mgr_actors}, fun mgr_actors/1}],
42
 
    {ok, Viewer} = et_viewer:start_link(Options),
43
 
    Collector = et_viewer:get_collector_pid(Viewer),      
 
47
    {ok, Viewer} = et_viewer:start_link(Options ++ ExtraOptions),
 
48
    Collector = et_viewer:get_collector_pid(Viewer),
44
49
    et_collector:report_event(Collector, 60, my_shell, mnesia_tm, start_outer, 
45
50
                              "Start outer transaction"),
46
51
    et_collector:report_event(Collector, 40, mnesia_tm, my_shell, new_tid, 
56
61
    et_collector:report_event(Collector, 60, my_shell, mnesia_tm, delete_transaction,
57
62
                              "End of outer transaction"),
58
63
    et_collector:report_event(Collector, 20, my_shell, end_outer,
59
 
                              "Transaction returned {atomic, ok}").
 
64
                              "Transaction returned {atomic, ok}"),
 
65
    {collector, Collector}.
 
66
 
60
67
%sim_trans
61
68
 
62
69
%mgr_actors
63
 
mgr_actors(E) when record(E, event) ->
 
70
mgr_actors(E) when is_record(E, event) ->
64
71
    Actor = fun(A) ->
65
72
               case A of
66
73
                   mnesia_tm     -> trans_mgr;
94
101
 
95
102
%live_trans
96
103
live_trans() ->
97
 
    et_demo:start([{title, "Mnesia tracer"},
98
 
                   {hide_actions, true},
99
 
                   {active_filter, named_process_info_nolink}]),
 
104
    live_trans([]).
 
105
 
 
106
live_trans(ExtraOptions) ->
 
107
    Options = [{title, "Mnesia tracer"},
 
108
               {hide_actions, true},
 
109
               {active_filter, named_process_info_nolink}],
 
110
    et_demo:start(Options ++ ExtraOptions),
100
111
    mnesia:start(),
101
112
    mnesia:create_table(my_tab, [{ram_copies, [node()]}]),
102
113
    et_demo:trace_mnesia(),
146
157
%filters
147
158
 
148
159
%module_as_actor
149
 
module_as_actor(E) when record(E, event) ->
 
160
module_as_actor(E) when is_record(E, event) ->
150
161
    case lists:keysearch(mfa, 1, E#event.contents) of
151
162
        {value, {mfa, {M, F, _A}}} ->
152
163
            case lists:keysearch(pam_result, 1, E#event.contents) of
163
174
%%----------------------------------------------------------------------
164
175
 
165
176
%plain_process_info
166
 
plain_process_info(E) when record(E, event) ->
 
177
plain_process_info(E) when is_record(E, event) ->
167
178
    case E#event.label of
168
179
        send                          -> true;
169
180
        send_to_non_existing_process  -> true;
182
193
%plain_process_info
183
194
 
184
195
%plain_process_info_nolink
185
 
plain_process_info_nolink(E) when record(E, event) ->
 
196
plain_process_info_nolink(E) when is_record(E, event) ->
186
197
    (E#event.label /= link) and
187
198
    (E#event.label /= unlink) and
188
199
    (E#event.label /= getting_linked) and
191
202
 
192
203
%%----------------------------------------------------------------------
193
204
 
194
 
named_process_info(E) when record(E, event) ->
 
205
named_process_info(E) when is_record(E, event) ->
195
206
    case plain_process_info(E) of
196
207
        true ->
197
208
            {true, E#event{to    = pid_to_name(E#event.to),
201
212
            false
202
213
    end.
203
214
 
204
 
named_process_info_nolink(E) when record(E, event) ->
 
215
named_process_info_nolink(E) when is_record(E, event) ->
205
216
    case plain_process_info_nolink(E) of
206
217
        true ->
207
218
            {true, E#event{to    = pid_to_name(E#event.to),
211
222
            false
212
223
    end.
213
224
 
214
 
pid_to_name(Pid) when pid(Pid) ->
 
225
pid_to_name(Pid) when is_pid(Pid) ->
215
226
    case process_info(Pid, registered_name) of
216
227
        {registered_name, Name} ->
217
228
            Name;
225
236
 
226
237
%%----------------------------------------------------------------------
227
238
 
228
 
node_process_info(E) when record(E, event) ->
 
239
node_process_info(E) when is_record(E, event) ->
229
240
    case plain_process_info(E) of
230
241
        true ->
231
242
            {true, E#event{to    = pid_to_node(E#event.to),
234
245
        false ->
235
246
            false
236
247
    end.
237
 
node_process_info_nolink(E) when record(E, event) ->
 
248
node_process_info_nolink(E) when is_record(E, event) ->
238
249
    case plain_process_info_nolink(E) of
239
250
        true ->
240
251
            {true, E#event{to    = pid_to_node(E#event.to),
244
255
            false
245
256
    end.
246
257
 
247
 
pid_to_node(Pid) when pid(Pid) ->
 
258
pid_to_node(Pid) when is_pid(Pid) ->
248
259
    node(Pid);
249
 
pid_to_node(Name) when atom(Name) ->
 
260
pid_to_node(Name) when is_atom(Name) ->
250
261
    node();
251
 
pid_to_node({_Name, Node}) when atom(Node) ->
 
262
pid_to_node({_Name, Node}) when is_atom(Node) ->
252
263
    Node.
253
264
 
254
265
%%----------------------------------------------------------------------
255
266
 
256
 
application_as_actor(E) when record(E, event) ->
 
267
application_as_actor(E) when is_record(E, event) ->
257
268
    {true, E#event{to    = pid_to_application(E#event.to),
258
269
                   from  = pid_to_application(E#event.from),
259
270
                   label = msg_to_label(E)}}.
260
271
 
261
 
pid_to_application(Pid) when pid(Pid) ->
 
272
pid_to_application(Pid) when is_pid(Pid) ->
262
273
    case application:get_application(Pid) of
263
274
        {ok, Name} ->
264
275
            Name;
268
279
 
269
280
%%----------------------------------------------------------------------
270
281
 
271
 
msg_to_label(E) when record(E, event) ->
 
282
msg_to_label(E) when is_record(E, event) ->
272
283
    case lists:keysearch(msg, 1, E#event.contents) of
273
284
        {value, {msg, Msg}} ->
274
285
            mnesia_msg_to_label(Msg, E#event.label);
349
360
        _                                          -> Label
350
361
    end.
351
362
 
 
363
%%----------------------------------------------------------------------
 
364
 
 
365
s() ->
 
366
    spawn(fun() -> t(), timer:sleep(infinity) end).
 
367
                  
 
368
t() ->
 
369
    t(500).
 
370
 
 
371
t(N) ->
 
372
    Collector = init(),
 
373
    gen(Collector, 1, N),
 
374
    Collector.
 
375
 
 
376
init() ->
 
377
    EvenFilter =
 
378
        fun(#event{label = Label}) ->
 
379
                case catch (list_to_integer(Label) div 10) rem 2 of
 
380
                    0 ->
 
381
                        false;
 
382
                    _ ->
 
383
                        true
 
384
                end
 
385
        end,
 
386
    OddFilter = fun(E) -> not EvenFilter(E) end,
 
387
    {ok, Viewer} = et_viewer:start_link([{dict_insert, {filter, odd_tens}, EvenFilter},
 
388
                                         {dict_insert, {filter, even_tens}, OddFilter},
 
389
                                         {active_filter, odd_tens}]),
 
390
    et_viewer:get_collector_pid(Viewer).
 
391
 
 
392
gen(Collector, From, To) ->
 
393
    [et_collector:report_event(Collector, 20, from, to, integer_to_list(I), [I]) || I <- lists:seq(From, To)], 
 
394
    ok.