~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/et/src/et_gs_viewer.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2009-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
%% Purpose: Displays a sequence chart for trace events (messages/actions)
 
21
%%----------------------------------------------------------------------
 
22
 
 
23
-module(et_gs_viewer).
 
24
 
 
25
-behaviour(gen_server).
 
26
 
 
27
%% External exports
 
28
-export([start_link/1]).
 
29
 
 
30
%% gen_server callbacks
 
31
-export([init/1, terminate/2, code_change/3,
 
32
         handle_call/3, handle_cast/2, handle_info/2]).
 
33
 
 
34
-include("../include/et.hrl").
 
35
-include("et_internal.hrl").
 
36
 
 
37
-define(unknown, "UNKNOWN").
 
38
 
 
39
-record(state,
 
40
        {parent_pid,       % Pid of parent process
 
41
         collector_pid,    % Pid of collector process
 
42
         event_order,      % Field to be used as primary key
 
43
         trace_pattern,    % Collector trace pattern
 
44
         active_filter,    % Name of the active filter
 
45
         filters,          % List of possible filters
 
46
         selected_actor,   % Actor selected by user
 
47
         first_event,      % Key of first event (regardless of visibility)
 
48
         last_event,       % Key of last event (regardless of visibility)
 
49
         max_events,       % Maximum number of shown events
 
50
         events,           % Queue containg all event keys (regardless of visibility)
 
51
         max_actors,       % Maximum number of shown actors
 
52
         actors,           % List of known actors
 
53
         refresh_needed,   % Refresh is needed in order to show all actors
 
54
         display_mode,     % Display all or only matching actors
 
55
         detail_level,     % Show only events with lesser detail level
 
56
         hide_actions,     % Hide/show events where to == from actor (bool)
 
57
         hide_unknown,     % Hide/show events with unknown actor (bool)
 
58
         is_suspended,     % Suspend viewer updates (bool)
 
59
         title,            % GUI: Window title
 
60
         win,              % GUI: Window object
 
61
         menubar,          % GUI: Menu bar object
 
62
         packer,           % GUI: Packer object
 
63
         width,            % GUI: Window width
 
64
         height,           % GUI: Window height
 
65
         scale,            % GUI: Scaling factor on canvas
 
66
         font,             % GUI: Font to be used on text labels
 
67
         canvas_width,     % GUI: Canvas width
 
68
         canvas_height,    % GUI: Canvas height
 
69
         canvas,           % GUI: Canvas object
 
70
         y_pos}).          % GUI: Current y position on canvas
 
71
 
 
72
-record(actor, {name, string}).
 
73
 
 
74
-define(initial_x, 10).
 
75
-define(incr_x,    60).
 
76
-define(initial_y, 15).
 
77
-define(incr_y,    15).
 
78
 
 
79
%%%----------------------------------------------------------------------
 
80
%%% Client side
 
81
%%%----------------------------------------------------------------------
 
82
 
 
83
start_link(Options) -> 
 
84
    case parse_opt(Options, default_state(), []) of
 
85
        {ok, S, CollectorOpt} ->
 
86
            case S#state.collector_pid of
 
87
                CollectorPid when is_pid(CollectorPid) ->
 
88
                    case gen_server:start_link(?MODULE, [S], []) of
 
89
                        {ok, Pid} when S#state.parent_pid =/= self() ->
 
90
                            unlink(Pid),
 
91
                            {ok, Pid};
 
92
                        Other ->
 
93
                            Other
 
94
                    end;
 
95
                undefined ->
 
96
                    case et_collector:start_link(CollectorOpt) of
 
97
                        {ok, CollectorPid} ->
 
98
                            S2 = S#state{collector_pid = CollectorPid},
 
99
                            case gen_server:start_link(?MODULE, [S2], []) of
 
100
                                {ok, Pid} when S#state.parent_pid =/= self() ->
 
101
                                    unlink(Pid),
 
102
                                    {ok, Pid};
 
103
                                Other ->
 
104
                                    Other
 
105
                            end;
 
106
                        {error, Reason} ->
 
107
                            {error, {et_collector, Reason}}
 
108
                    end
 
109
            end;
 
110
        {error, Reason} ->
 
111
            {error, Reason}
 
112
    end.
 
113
 
 
114
default_state() ->
 
115
    #state{parent_pid     = self(),
 
116
           collector_pid  = undefined,
 
117
           detail_level   = ?detail_level_max,
 
118
           active_filter  = ?DEFAULT_FILTER_NAME,
 
119
           filters        = [?DEFAULT_FILTER],
 
120
           event_order    = trace_ts,
 
121
           is_suspended   = false,
 
122
           max_events     = 100,
 
123
           first_event    = first,
 
124
           last_event     = first,
 
125
           events         = queue_new(),
 
126
           max_actors     = 5,
 
127
           actors         = [create_actor(?unknown)],
 
128
           selected_actor = ?unknown,
 
129
           hide_actions   = false,
 
130
           hide_unknown   = false,
 
131
           refresh_needed = false,
 
132
           display_mode   = all,
 
133
           scale          = 2,
 
134
           canvas_height  = 0,
 
135
           canvas_width   = 0,
 
136
           width          = 800,
 
137
           height         = 600}.
 
138
 
 
139
parse_opt([], S, CollectorOpt) ->
 
140
    {ok, S, [{parent_pid, S#state.parent_pid} | CollectorOpt]};
 
141
parse_opt([H | T], S, CollectorOpt) ->
 
142
    case H of
 
143
        {parent_pid, Parent} when Parent =:= undefined ->
 
144
            CollectorOpt2 = [H | CollectorOpt],
 
145
            parse_opt(T, S#state{parent_pid = Parent}, CollectorOpt2);
 
146
        {parent_pid, Parent} when is_pid(Parent) ->
 
147
            CollectorOpt2 = [H | CollectorOpt],
 
148
            parse_opt(T, S#state{parent_pid = Parent}, CollectorOpt2);
 
149
        {title, Title} ->
 
150
            parse_opt(T, S#state{title = name_to_string(Title)}, CollectorOpt);
 
151
        {detail_level, Level} when is_integer(Level),
 
152
                                   Level >= ?detail_level_min,
 
153
                                   Level =< ?detail_level_max -> 
 
154
            parse_opt(T, S#state{detail_level = Level}, CollectorOpt);
 
155
        {detail_level, max} ->
 
156
            parse_opt(T, S#state{detail_level = ?detail_level_max}, CollectorOpt);
 
157
        {detail_level, min} ->
 
158
            parse_opt(T, S#state{detail_level = ?detail_level_min}, CollectorOpt);
 
159
        {is_suspended, true} ->
 
160
            parse_opt(T, S#state{is_suspended = true}, CollectorOpt);
 
161
        {is_suspended, false} ->
 
162
            parse_opt(T, S#state{is_suspended = false}, CollectorOpt);
 
163
        {scale, Scale} when is_integer(Scale), Scale > 0 ->
 
164
            parse_opt(T, S#state{scale = Scale}, CollectorOpt);
 
165
        {width, W} when is_integer(W), W > 0 ->
 
166
            parse_opt(T, S#state{width = W, canvas_width = W}, CollectorOpt);
 
167
        {height, WH} when is_integer(WH), WH > 0 ->
 
168
            parse_opt(T, S#state{height = WH, canvas_height = WH}, CollectorOpt);
 
169
        {collector_pid, Pid} when is_pid(Pid) -> 
 
170
            parse_opt(T, S#state{collector_pid = Pid}, CollectorOpt);
 
171
        {collector_pid, undefined} -> 
 
172
            parse_opt(T, S#state{collector_pid = undefined}, CollectorOpt);
 
173
        {active_filter, Name} when is_atom(Name) ->
 
174
            parse_opt(T, S#state{active_filter = Name}, CollectorOpt);
 
175
        {event_order, trace_ts} -> %% BUGBUG: Verify event_order with collector
 
176
            CollectorOpt2 = [H | CollectorOpt],
 
177
            parse_opt(T, S#state{event_order = trace_ts}, CollectorOpt2);
 
178
        {event_order, event_ts} -> %% BUGBUG: Verify event_order with collector
 
179
            CollectorOpt2 = [H | CollectorOpt],
 
180
            parse_opt(T, S#state{event_order = event_ts}, CollectorOpt2);
 
181
        {trace_port, _Port} -> 
 
182
            CollectorOpt2 = [H | CollectorOpt],
 
183
            parse_opt(T, S, CollectorOpt2);
 
184
        {trace_max_queue, _Queue} -> 
 
185
            CollectorOpt2 = [H | CollectorOpt],
 
186
            parse_opt(T, S, CollectorOpt2);
 
187
        {trace_pattern, _Pattern} -> 
 
188
            CollectorOpt2 = [H | CollectorOpt],
 
189
            parse_opt(T, S, CollectorOpt2);
 
190
        {trace_global, _Boolean} -> 
 
191
            CollectorOpt2 = [H | CollectorOpt],
 
192
            parse_opt(T, S, CollectorOpt2);
 
193
        {trace_client, _Client} -> 
 
194
            CollectorOpt2 = [H | CollectorOpt],
 
195
            parse_opt(T, S, CollectorOpt2);
 
196
        {dict_insert, {filter, Name}, Fun} ->
 
197
            if
 
198
                is_atom(Name), is_function(Fun) ->
 
199
                    F = #filter{name = Name, function = Fun},
 
200
                    Filters = lists:keydelete(Name, #filter.name, S#state.filters),
 
201
                    CollectorOpt2 = [H | CollectorOpt],
 
202
                    parse_opt(T, S#state{filters = Filters ++ [F]}, CollectorOpt2);
 
203
                true ->
 
204
                    {error, {bad_option, H}}
 
205
            end;
 
206
        {dict_insert, {subscriber, Pid}, _Val} ->
 
207
            if
 
208
                is_pid(Pid) ->
 
209
                    CollectorOpt2 = [H | CollectorOpt],
 
210
                    parse_opt(T, S, CollectorOpt2);
 
211
                true ->
 
212
                    {error, {bad_option, H}}
 
213
            end;
 
214
        {dict_insert, _Key, _Val} ->
 
215
            CollectorOpt2 = [H | CollectorOpt],
 
216
            parse_opt(T, S, CollectorOpt2);
 
217
        {dict_delete, {filter, Name}} ->
 
218
            Filters = lists:keydelete(Name, #filter.name, S#state.filters),
 
219
            CollectorOpt2 = [H | CollectorOpt],
 
220
            parse_opt(T, S#state{filters = Filters}, CollectorOpt2);
 
221
        {dict_delete, _Key} ->
 
222
            CollectorOpt2 = [H | CollectorOpt],
 
223
            parse_opt(T, S, CollectorOpt2);
 
224
        {max_events, Max} when is_integer(Max), Max > 0->
 
225
            parse_opt(T,  S#state{max_events = Max}, CollectorOpt);
 
226
        {max_events, Max} when Max =:= infinity ->
 
227
            parse_opt(T,  S#state{max_events = Max}, CollectorOpt);
 
228
        {max_actors, Max} when is_integer(Max), Max >= 0->
 
229
            parse_opt(T,  S#state{max_actors = Max}, CollectorOpt);
 
230
        {max_actors, Max} when Max =:= infinity ->
 
231
            parse_opt(T,  S#state{max_actors = Max}, CollectorOpt);
 
232
        {actors, ActorNames} when is_list(ActorNames) ->
 
233
            ActorNames2 = 
 
234
                case lists:member(?unknown, ActorNames) of
 
235
                    false -> [?unknown | ActorNames];
 
236
                    true  -> ActorNames
 
237
                end,
 
238
            Actors = [create_actor(Name) || Name <- ActorNames2],
 
239
            parse_opt(T, S#state{actors = Actors}, CollectorOpt);
 
240
        {first_event, First} ->
 
241
            parse_opt(T,  S#state{first_event = First}, CollectorOpt);
 
242
        {hide_unknown, Bool} when Bool =:= false ->
 
243
            parse_opt(T,  S#state{hide_unknown = Bool}, CollectorOpt);
 
244
        {hide_unknown, Bool} when Bool =:= true ->
 
245
            parse_opt(T,  S#state{hide_unknown = Bool}, CollectorOpt);
 
246
        {hide_actions, Bool} when Bool =:= false ->
 
247
            parse_opt(T,  S#state{hide_actions = Bool}, CollectorOpt);
 
248
        {hide_actions, Bool} when Bool =:= true ->
 
249
            parse_opt(T,  S#state{hide_actions = Bool}, CollectorOpt);
 
250
        {display_mode, Mode = all} ->
 
251
            parse_opt(T,  S#state{display_mode = Mode}, CollectorOpt);
 
252
        {display_mode, Mode = {search_actors, Dir, _Key, Actors}} when is_list(Actors), Dir =:= forward ->
 
253
            parse_opt(T,  S#state{display_mode = Mode}, CollectorOpt);
 
254
        {display_mode, Mode = {search_actors, Dir, _Key, Actors}} when is_list(Actors), Dir =:= reverse ->
 
255
            parse_opt(T,  S#state{display_mode = Mode}, CollectorOpt);
 
256
 
 
257
        Bad ->
 
258
            {error, {bad_option, Bad}}
 
259
    end;
 
260
parse_opt(BadList, _S, _CollectorOpt) ->
 
261
    {error, {bad_option_list, BadList}}.
 
262
 
 
263
do_dict_insert({filter, Name}, Fun, S) when is_atom(Name), is_function(Fun) ->
 
264
    F = #filter{name = Name, function = Fun},
 
265
    Filters = lists:keydelete(Name, #filter.name, S#state.filters),
 
266
    Filters2 = lists:keysort(#filter.name, [F | Filters]),
 
267
    gs:destroy(filter_menu),
 
268
    create_filter_menu(S#state.active_filter, Filters2),    
 
269
    S#state{filters = Filters2};
 
270
do_dict_insert(_Key, _Val, S) ->
 
271
    %% ok = error_logger:format("~p(~p): handle_info({et, {dict_insert, ~p, ~p}})~n",
 
272
    %%                          [?MODULE, self(), Key, Val]),
 
273
    S.
 
274
 
 
275
do_dict_delete({filter, Name}, S) when is_atom(Name), Name =/= S#state.active_filter ->
 
276
    Filters = lists:keydelete(Name, #filter.name, S#state.filters),
 
277
    gs:destroy(filter_menu),
 
278
    create_filter_menu(S#state.active_filter, Filters),    
 
279
    S#state{filters = Filters};
 
280
do_dict_delete(_Key, S) ->
 
281
    %% ok = error_logger:format("~p(~p): handle_info({et, {dict_delete, ~p}})~n",
 
282
    %%                          [?MODULE, self(), Key]),
 
283
    S.
 
284
 
 
285
%%%----------------------------------------------------------------------
 
286
%%% Callback functions from gen_server
 
287
%%%----------------------------------------------------------------------
 
288
 
 
289
%%----------------------------------------------------------------------
 
290
%% Func: init/1
 
291
%% Returns: {ok, State}          |
 
292
%%          {ok, State, Timeout} |
 
293
%%          ignore               |
 
294
%%          {stop, Reason}
 
295
%%----------------------------------------------------------------------
 
296
 
 
297
init([S]) when is_record(S, state) ->
 
298
    process_flag(trap_exit, true),
 
299
    InitialTimeout = 0,
 
300
    case S#state.parent_pid of
 
301
        undefined ->
 
302
            ignore;
 
303
        Pid when is_pid(Pid) ->
 
304
            link(Pid)
 
305
    end,
 
306
    et_collector:dict_insert(S#state.collector_pid,
 
307
                             {subscriber, self()},
 
308
                             ?MODULE),
 
309
    {ok, create_main_window(S), InitialTimeout}.
 
310
 
 
311
%%----------------------------------------------------------------------
 
312
%% Func: handle_call/3
 
313
%% Returns: {reply, Reply, State}          |
 
314
%%          {reply, Reply, State, Timeout} |
 
315
%%          {noreply, State}               |
 
316
%%          {noreply, State, Timeout}      |
 
317
%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
 
318
%%          {stop, Reason, State}            (terminate/2 is called)
 
319
%%----------------------------------------------------------------------
 
320
 
 
321
handle_call(get_collector_pid, _From, S) ->
 
322
    Reply = S#state.collector_pid,
 
323
    reply(Reply, S);
 
324
handle_call(stop, _From, S) ->
 
325
    gs:destroy(S#state.win),
 
326
    {stop, shutdown, ok, S};
 
327
handle_call(Request, From, S) ->
 
328
    ok = error_logger:format("~p(~p): handle_call(~p, ~p, ~p)~n",
 
329
                             [?MODULE, self(), Request, From, S]),
 
330
    Reply = {error, {bad_request, Request}},
 
331
    reply(Reply, S).
 
332
 
 
333
%%----------------------------------------------------------------------
 
334
%% Func: handle_cast/2
 
335
%% Returns: {noreply, State}          |
 
336
%%          {noreply, State, Timeout} |
 
337
%%          {stop, Reason, State}            (terminate/2 is called)
 
338
%%----------------------------------------------------------------------
 
339
 
 
340
handle_cast(Msg, S) ->
 
341
    ok = error_logger:format("~p(~p): handle_cast(~p, ~p)~n",
 
342
                             [?MODULE, self(), Msg, S]),
 
343
    noreply(S).
 
344
 
 
345
%%----------------------------------------------------------------------
 
346
%% Func: handle_info/2
 
347
%% Returns: {noreply, State}          |
 
348
%%          {noreply, State, Timeout} |
 
349
%%          {stop, Reason, State}            (terminate/2 is called)
 
350
%%----------------------------------------------------------------------
 
351
 
 
352
handle_info({et, {more_events, _Size}}, S) ->
 
353
    noreply(S);
 
354
handle_info({et, {insert_actors, ActorNames}}, S) when is_list(ActorNames) ->
 
355
    Fun = fun(N, Actors) ->
 
356
                  case lists:keymember(N, #actor.name, Actors) of
 
357
                      true  -> Actors;
 
358
                      false -> Actors ++ [create_actor(N)]
 
359
                  end
 
360
          end,
 
361
    Actors = lists:foldl(Fun, S#state.actors, ActorNames),
 
362
    S2 = refresh_main_window(S#state{actors = Actors}),
 
363
    noreply(S2);
 
364
handle_info({et, {delete_actors, ActorNames}}, S) when is_list(ActorNames)->
 
365
    Fun = fun(N, Actors) when N =:= ?unknown ->
 
366
                  Actors;
 
367
             (N, Actors) ->
 
368
                  lists:keydelete(N, #actor.name, Actors)
 
369
          end,
 
370
    New = lists:foldl(Fun, S#state.actors, ActorNames),
 
371
    S2 = refresh_main_window(S#state{actors = New}),
 
372
    noreply(S2);
 
373
handle_info({et, {dict_insert, Key, Val}}, S) ->
 
374
    S2 = do_dict_insert(Key, Val, S),
 
375
    noreply(S2);
 
376
handle_info({et, {dict_delete, Key}}, S) ->
 
377
    S2 = do_dict_delete(Key, S),
 
378
    noreply(S2);
 
379
handle_info({et, first}, S) ->
 
380
    S2 = scroll_first(S),
 
381
    noreply(S2);
 
382
handle_info({et, prev}, S) ->
 
383
    S2 = scroll_prev(S),
 
384
    noreply(S2);
 
385
handle_info({et, next}, S) ->
 
386
    S2 = scroll_next(S),
 
387
    noreply(S2);
 
388
handle_info({et, last}, S) ->
 
389
    S2 = scroll_last(S),
 
390
    noreply(S2);
 
391
handle_info({et, refresh}, S) ->
 
392
    S2 = refresh_main_window(S),
 
393
    noreply(S2);
 
394
handle_info({et, {display_mode, Mode}}, S) ->
 
395
    S2 = change_display_mode(Mode, S),
 
396
    noreply(S2);
 
397
handle_info({et, close}, S) ->
 
398
    gs:destroy(S#state.win),
 
399
    {stop, shutdown, S};
 
400
handle_info({gs, Button, click, Data, Other} = Click, S) ->
 
401
    CollectorPid = S#state.collector_pid,
 
402
    case Button of
 
403
        close ->
 
404
            gs:destroy(S#state.win),
 
405
            {stop, shutdown, S};
 
406
        suspended ->
 
407
            case Other of
 
408
                [_Text, _Group, Bool | _] when Bool =:= true ->
 
409
                    S2 = do_suspend(S),
 
410
                    noreply(S2);    
 
411
                [_Text, _Group, Bool | _] when Bool =:= false ->
 
412
                    S2 = do_resume(S),
 
413
                    noreply(S2);
 
414
                _ ->
 
415
                    click_error(Click, S),
 
416
                    noreply(S)
 
417
            end;
 
418
        hide_actions ->
 
419
            case Other of
 
420
                [_Text, _Group, Bool | _] when Bool =:= true ->
 
421
                    S2 = refresh_main_window(S#state{hide_actions = Bool}),
 
422
                    noreply(S2);    
 
423
                [_Text, _Group, Bool | _] when Bool =:= false ->
 
424
                    S2 = refresh_main_window(S#state{hide_actions = Bool}),
 
425
                    noreply(S2);
 
426
                _ -> 
 
427
                    click_error(Click, S),
 
428
                    noreply(S)
 
429
            end;
 
430
        hide_unknown ->
 
431
            case Other of
 
432
                [_Text, _Group, Bool | _] when Bool =:= true ->
 
433
                    S2 = refresh_main_window(S#state{hide_unknown = Bool}),
 
434
                    noreply(S2);    
 
435
                [_Text, _Group, Bool | _] when Bool =:= false ->
 
436
                    S2 = refresh_main_window(S#state{hide_unknown = Bool}),
 
437
                    noreply(S2);
 
438
                _ -> 
 
439
                    click_error(Click, S),
 
440
                    noreply(S)
 
441
            end;
 
442
        up ->
 
443
            S2 = scroll_up(S),
 
444
            noreply(S2);
 
445
        down ->
 
446
            S2 = scroll_down(S),
 
447
            noreply(S2);
 
448
        first ->
 
449
            S2 = scroll_first(S),
 
450
            noreply(S2);
 
451
        prev ->
 
452
            S2 = scroll_prev(S),
 
453
            noreply(S2);
 
454
        next ->
 
455
            S2 = scroll_next(S),
 
456
            noreply(S2);
 
457
        last ->
 
458
            S2 = scroll_last(S),
 
459
            noreply(S2);
 
460
        refresh ->
 
461
            S2 = refresh_main_window(S),
 
462
            noreply(S2);
 
463
        {display_mode, Mode} ->
 
464
            S2 = change_display_mode(Mode, S),
 
465
            noreply(S2);
 
466
        close_all ->
 
467
            close_all(S);
 
468
        close_all_others ->
 
469
            close_all_others(S);
 
470
        first_all ->
 
471
            et_collector:multicast(CollectorPid, first),
 
472
            noreply(S);
 
473
        prev_all ->
 
474
            et_collector:multicast(CollectorPid, prev),
 
475
            noreply(S);
 
476
        next_all ->
 
477
            et_collector:multicast(CollectorPid, next),
 
478
            noreply(S);
 
479
        last_all ->
 
480
            et_collector:multicast(CollectorPid, last),
 
481
            noreply(S);
 
482
        refresh_all ->
 
483
            et_collector:multicast(CollectorPid, refresh),
 
484
            noreply(S);
 
485
        clear_all ->
 
486
            et_collector:clear_table(CollectorPid),
 
487
            et_collector:multicast(CollectorPid, refresh),
 
488
            noreply(S);
 
489
        load_all ->
 
490
            et_collector:start_trace_client(CollectorPid, event_file, "et_viewer.log"),
 
491
            noreply(S);
 
492
        save_all ->
 
493
            et_collector:save_event_file(CollectorPid,
 
494
                                         "et_viewer.log",
 
495
                                         [existing, write, keep]),
 
496
            noreply(S);
 
497
        {open_viewer, Scale} ->
 
498
            Actors = [A#actor.name || A <- S#state.actors],
 
499
            open_viewer(Scale, S#state.active_filter, Actors, S),
 
500
            noreply(S);
 
501
        _Level when Data =:= detail_level, is_integer(hd(Other)),
 
502
                    hd(Other) >= ?detail_level_min,
 
503
                    hd(Other) =< ?detail_level_max ->
 
504
            S2 = S#state{detail_level = hd(Other)},
 
505
            noreply(S2);
 
506
        _PopupMenuItem when is_record(Data, filter) ->
 
507
            open_viewer(S#state.scale, Data#filter.name, [?unknown], S),
 
508
            noreply(S);
 
509
        _ ->
 
510
            click_error(Click, S),
 
511
            noreply(S)
 
512
    end;
 
513
handle_info({gs, _Obj, destroy,_, _}, S) ->
 
514
    gs:destroy(S#state.win),
 
515
    {stop, shutdown, S};
 
516
handle_info({gs, _Obj, buttonpress, _, [_Button, X, Y | _]}, S) ->
 
517
    S3 =
 
518
        case y_to_n(Y, S) of
 
519
            actor ->
 
520
                %% Actor click
 
521
                case S#state.actors of
 
522
                    [] ->
 
523
                        S;
 
524
                    _ ->
 
525
                        N = x_to_n(X, S),
 
526
                        A = lists:nth(N, S#state.actors),
 
527
                        S#state{selected_actor = A}
 
528
                end;
 
529
            {event, N} ->
 
530
                %% Event click
 
531
                List = queue_to_list(S#state.events),
 
532
                S2 = S#state{events = list_to_queue(List)},
 
533
                
 
534
                Key = lists:nth(N, List),
 
535
                Pid = S#state.collector_pid,
 
536
                Fun = fun create_contents_window/2,
 
537
                case et_collector:iterate(Pid, Key, -1) of
 
538
                    Prev when Prev =:= Key ->
 
539
                        et_collector:iterate(Pid, first, 1, Fun, S2);
 
540
                    Prev ->
 
541
                        et_collector:iterate(Pid, Prev, 1, Fun, S2)
 
542
                end
 
543
        end,
 
544
    noreply(S3);
 
545
handle_info({gs, _Obj, buttonrelease, _, [_Button, X, Y | _]}, S) ->
 
546
    S2 =
 
547
        case y_to_n(Y, S) of
 
548
            actor ->
 
549
                %% Actor click
 
550
                case S#state.actors of
 
551
                    [] ->
 
552
                        S;
 
553
                    Actors ->
 
554
                        N = x_to_n(X, S),
 
555
                        New = lists:nth(N, S#state.actors),
 
556
                        Old = S#state.selected_actor,
 
557
                        case New#actor.name =:= Old#actor.name of
 
558
                            true ->
 
559
                                A = S#state.selected_actor,
 
560
                                toggle_search_for_actor(A#actor.name, S);
 
561
                            false ->
 
562
                                move_actor(Old, New, Actors, S)
 
563
                        end
 
564
                end;
 
565
            {event, _N} ->
 
566
                %% Event click ignored
 
567
                S
 
568
        end,
 
569
    noreply(S2);
 
570
handle_info({gs, _Obj, keypress, _, [KeySym, _Keycode, _Shift, _Control | _]} = Key, S) ->
 
571
    case KeySym of
 
572
        'c' ->
 
573
            close_all_others(S);
 
574
        'C' ->
 
575
            close_all(S);
 
576
        'Up' ->
 
577
            S2 = scroll_up(S),
 
578
            noreply(S2);
 
579
        'Down' ->
 
580
            S2 = scroll_down(S),
 
581
            noreply(S2);
 
582
        'f' ->
 
583
            S2 = scroll_first(S),
 
584
            noreply(S2);
 
585
        'p' ->
 
586
            S2 = scroll_prev(S),
 
587
            noreply(S2);
 
588
        'Prior' ->
 
589
            S2 = scroll_prev(S),
 
590
            noreply(S2);
 
591
        'n' ->
 
592
            S2 = scroll_next(S),
 
593
            noreply(S2);
 
594
        'Next' ->
 
595
            S2 = scroll_next(S),
 
596
            noreply(S2);
 
597
        'l' ->
 
598
            S2 = scroll_last(S),
 
599
            noreply(S2);
 
600
        'r' ->
 
601
            S2 = refresh_main_window(S),
 
602
            noreply(S2);
 
603
        'F' ->
 
604
            et_collector:multicast(S#state.collector_pid, first),
 
605
            noreply(S);
 
606
        'P' ->
 
607
            et_collector:multicast(S#state.collector_pid, prev),
 
608
            noreply(S);
 
609
        'N' ->
 
610
            et_collector:multicast(S#state.collector_pid, next),
 
611
            noreply(S);
 
612
        'L' ->
 
613
            et_collector:multicast(S#state.collector_pid, last),
 
614
            noreply(S);
 
615
        'R' ->
 
616
            et_collector:multicast(S#state.collector_pid, refresh),
 
617
            noreply(S);
 
618
 
 
619
        'a' ->
 
620
            S2 = S#state{display_mode = all},
 
621
            S3 = refresh_main_window(S2),
 
622
            noreply(S3);
 
623
 
 
624
        'equal' ->
 
625
            Scale = S#state.scale,
 
626
            Actors = [A#actor.name || A <- S#state.actors],
 
627
            open_viewer(Scale, S#state.active_filter, Actors, S),
 
628
            noreply(S);
 
629
        'plus' ->
 
630
            Scale = S#state.scale + 1,
 
631
            Actors = [A#actor.name || A <- S#state.actors],
 
632
            open_viewer(Scale, S#state.active_filter, Actors, S),
 
633
            noreply(S);
 
634
        'minus' ->
 
635
            case S#state.scale of
 
636
                1 ->
 
637
                    gs:config(S#state.canvas, beep);
 
638
                Scale ->
 
639
                    Actors = [A#actor.name || A <- S#state.actors],
 
640
                    open_viewer(Scale - 1, S#state.active_filter, Actors, S)
 
641
            end,
 
642
            noreply(S);
 
643
        0 ->
 
644
            case lists:keysearch(?DEFAULT_FILTER_NAME, #filter.name, S#state.filters) of
 
645
                {value, F} when is_record(F, filter) ->
 
646
                    open_viewer(S#state.scale, F#filter.name, [?unknown], S);
 
647
                false ->
 
648
                    gs:config(S#state.canvas, beep)
 
649
            end,
 
650
            noreply(S);
 
651
        Int when is_integer(Int), Int > 0, Int =< 9 ->
 
652
            case catch lists:nth(Int, S#state.filters) of
 
653
                F when is_record(F, filter) ->
 
654
                    open_viewer(S#state.scale, F#filter.name, [?unknown], S);
 
655
                {'EXIT', _} ->
 
656
                    gs:config(S#state.canvas, beep)
 
657
            end,
 
658
            noreply(S);
 
659
 
 
660
        'Shift_L' ->
 
661
            noreply(S);
 
662
        'Shift_R' ->
 
663
            noreply(S);
 
664
        'Caps_Lock' ->
 
665
            noreply(S);
 
666
            
 
667
        _ ->
 
668
            click_error(Key, S),
 
669
            noreply(S)
 
670
    end;
 
671
handle_info({gs, _Obj,configure, [], [W, H | _]}, S) ->
 
672
    gs:config(S#state.packer, [{width, W}, {height, H}]),
 
673
    S2 = S#state{width = W, height = H},
 
674
    noreply(S2);
 
675
handle_info(timeout, S) ->
 
676
    Try =
 
677
        case S#state.display_mode of
 
678
            {search_actors, reverse, _, _} ->
 
679
                -10;
 
680
            _ ->
 
681
                10
 
682
        end,
 
683
    if
 
684
        S#state.is_suspended =:= true ->
 
685
            {noreply, S, infinity};
 
686
        S#state.max_events =:= infinity ->
 
687
            display_more_events(Try, S);
 
688
        true ->
 
689
            Needed = S#state.max_events - queue_length(S#state.events),
 
690
            if
 
691
                Needed =< 0  -> {noreply, S, infinity};
 
692
                Needed > 10  -> display_more_events(Try, S);
 
693
                Needed =< 10 -> display_more_events(Needed, S)
 
694
            end
 
695
    end;
 
696
 
 
697
handle_info({'EXIT', Pid, Reason}, S) ->
 
698
    if
 
699
        Pid =:= S#state.collector_pid ->
 
700
            unlink(Pid),
 
701
            gs:destroy(S#state.win),
 
702
            {stop, Reason, S};
 
703
        Pid =:= S#state.parent_pid ->
 
704
            unlink(Pid),
 
705
            gs:destroy(S#state.win),
 
706
            {stop, Reason, S};
 
707
        true ->
 
708
            noreply(S)
 
709
    end;
 
710
handle_info(Info, S) ->
 
711
    ok = error_logger:format("~p(~p): handle_info(~p, ~p)~n",
 
712
                             [?MODULE, self(), Info, S]),
 
713
    noreply(S).
 
714
 
 
715
%%----------------------------------------------------------------------
 
716
%% Func: terminate/2
 
717
%% Purpose: Shutdown the server
 
718
%% Returns: any (ignored by gen_server)
 
719
%%----------------------------------------------------------------------
 
720
 
 
721
terminate(_Reason, _S) ->
 
722
    ignore.
 
723
 
 
724
%%----------------------------------------------------------------------
 
725
%% Func: code_change/3
 
726
%% Purpose: Convert process state when code is changed
 
727
%% Returns: {ok, NewState}
 
728
%%----------------------------------------------------------------------
 
729
 
 
730
code_change(_OldVsn, S, _Extra) ->
 
731
    {ok, S}.
 
732
 
 
733
%%%----------------------------------------------------------------------
 
734
%%% Handle suspend/resume
 
735
%%%----------------------------------------------------------------------
 
736
 
 
737
reply(Reply, S) ->
 
738
    case queue_length(S#state.events) of
 
739
        _ when S#state.is_suspended =:= true ->
 
740
            {reply, Reply, S, infinity};
 
741
        _ when S#state.max_events =:= infinity ->
 
742
            {reply, Reply, S, 500};
 
743
        N when N >= S#state.max_events ->
 
744
            {reply, Reply, S, infinity};
 
745
        _ ->
 
746
            {reply, Reply, S, 0}
 
747
    end.
 
748
 
 
749
noreply(S) ->
 
750
    case queue_length(S#state.events) of
 
751
        _ when S#state.is_suspended =:= true ->
 
752
            {noreply, S, infinity};
 
753
        _ when S#state.max_events =:= infinity ->
 
754
            {noreply, S, 500};
 
755
        N when N >= S#state.max_events ->
 
756
            {noreply, S, infinity};
 
757
        _ ->
 
758
            {noreply, S, 0}
 
759
    end.
 
760
 
 
761
do_suspend(S) ->
 
762
    config_suspend(S#state{is_suspended = true}).
 
763
 
 
764
do_resume(S) ->
 
765
    config_suspend(S#state{is_suspended = false}).
 
766
 
 
767
config_suspend(S) ->
 
768
    Suspended = S#state.is_suspended,
 
769
    gs:config(refresh,     [{enable, not Suspended}]),
 
770
    gs:config(refresh_all, [{enable, not Suspended}]),
 
771
    gs:config(clear_all,   [{enable, not Suspended}]),
 
772
    S.
 
773
 
 
774
refresh_main_window(S) ->
 
775
    Pid = S#state.collector_pid,
 
776
    Key = S#state.first_event,
 
777
    case et_collector:iterate(Pid, Key, -1) of
 
778
        Prev when Prev =:= Key ->
 
779
            scroll_first(S);
 
780
        _Prev ->
 
781
            S2 = S#state{last_event = S#state.first_event},
 
782
            clear_canvas(S2)
 
783
    end.    
 
784
 
 
785
scroll_first(S) ->
 
786
    S2 = S#state{first_event = first, last_event  = first},
 
787
    clear_canvas(S2).
 
788
 
 
789
scroll_prev(S) ->
 
790
    Try =
 
791
        case S#state.max_events of
 
792
            infinity -> -10;
 
793
            Max      -> -Max
 
794
        end,
 
795
    Key = et_collector:iterate(S#state.collector_pid, S#state.first_event, Try),
 
796
    S2 = S#state{first_event = Key, last_event  = Key},
 
797
    clear_canvas(S2).
 
798
 
 
799
scroll_next(S) ->
 
800
    S2 = S#state{first_event = S#state.last_event},
 
801
    clear_canvas(S2).
 
802
 
 
803
scroll_up(S) ->
 
804
    Key = et_collector:iterate(S#state.collector_pid, S#state.first_event, -5),
 
805
    S2 = S#state{first_event = Key, last_event  = Key},
 
806
    clear_canvas(S2).
 
807
 
 
808
scroll_down(S) ->
 
809
    Key = et_collector:iterate(S#state.collector_pid, S#state.first_event, 5),
 
810
    S2 = S#state{first_event = Key, last_event  = Key},
 
811
    clear_canvas(S2).
 
812
 
 
813
scroll_last(S) ->
 
814
    S2 = S#state{first_event = last, last_event  = last},
 
815
    clear_canvas(S2).
 
816
 
 
817
change_display_mode(Mode, S) ->
 
818
    case Mode of
 
819
        all ->
 
820
            S2 = S#state{display_mode = Mode},
 
821
            refresh_main_window(S2);
 
822
        {search_actors, _Dir, _Key, []}  ->
 
823
            S2 = S#state{display_mode = all},
 
824
            refresh_main_window(S2);
 
825
        {search_actors, _Dir, Key, Actors} when is_list(Actors) ->
 
826
            Pid = S#state.collector_pid,
 
827
            Prev = et_collector:iterate(Pid, Key, -1),
 
828
            S2 = S#state{first_event  = Prev,
 
829
                         last_event   = Prev,
 
830
                         display_mode = Mode},
 
831
            clear_canvas(S2)
 
832
    end.
 
833
 
 
834
close_all(S) ->
 
835
    et_collector:multicast(S#state.collector_pid, close),
 
836
    timer:sleep(timer:seconds(1)),
 
837
    spawn(et_collector, stop, [S#state.collector_pid]),
 
838
    gs:destroy(S#state.win),
 
839
    {stop, shutdown, S}.
 
840
 
 
841
close_all_others(S) ->
 
842
    Fun =
 
843
        fun({{subscriber, Pid}, _}) ->
 
844
                if
 
845
                    Pid =:= self() ->
 
846
                        ignore;
 
847
                    true ->
 
848
                        unlink(Pid),
 
849
                        Pid ! {et, close}
 
850
                end
 
851
        end,
 
852
    All = et_collector:dict_match(S#state.collector_pid,
 
853
                                  {{subscriber, '_'}, '_'}),
 
854
    lists:foreach(Fun, All),
 
855
    noreply(S).
 
856
 
 
857
click_error(Click, S) ->
 
858
    gs:config(S#state.canvas, beep),
 
859
    io:format("~p: ignored: ~p~n", [?MODULE, Click]).
 
860
 
 
861
%%%----------------------------------------------------------------------
 
862
%%% Clone viewer
 
863
%%%----------------------------------------------------------------------
 
864
 
 
865
open_viewer(Scale, FilterName, Actors, S) ->
 
866
    Filters = [{dict_insert, {filter, F#filter.name}, F#filter.function}
 
867
               || F <- S#state.filters],
 
868
    Options = 
 
869
        [{parent_pid,    S#state.parent_pid},
 
870
         {title,         S#state.title},
 
871
         {collector_pid, S#state.collector_pid},
 
872
         {is_suspended,  S#state.is_suspended},
 
873
         {detail_level,  S#state.detail_level},
 
874
         {active_filter, FilterName},
 
875
         {event_order,   S#state.event_order},
 
876
         {first_event,   S#state.first_event},
 
877
         {max_events,    S#state.max_events},
 
878
         {max_actors,    S#state.max_actors},
 
879
         {hide_actions,  S#state.hide_actions},
 
880
         {hide_unknown,  S#state.hide_unknown},
 
881
         {is_suspended,  S#state.is_suspended},
 
882
         {actors,        Actors},
 
883
         {scale,         Scale},
 
884
         {width,         S#state.width},
 
885
         {height,        S#state.height} | Filters],
 
886
    case start_link(Options) of
 
887
        {ok, ViewerPid} ->
 
888
            unlink(ViewerPid),
 
889
            ok;
 
890
        {error, Reason} ->
 
891
            ok = error_logger:format("~p: Failed to start a new window: ~p~n",
 
892
                                     [?MODULE, Reason])
 
893
    end.
 
894
 
 
895
%%%----------------------------------------------------------------------
 
896
%%% Handle graphics
 
897
%%%----------------------------------------------------------------------
 
898
 
 
899
create_main_window(S) ->
 
900
    Font    = select_font(S#state.scale),
 
901
    GS      = gs:start(),
 
902
    Name    = name_to_string(S#state.active_filter),
 
903
    Title   = case S#state.title of
 
904
                  undefined -> atom_to_list(?MODULE);
 
905
                  Explicit  -> name_to_string(Explicit)
 
906
              end,
 
907
    WinOpt  = [{title, Title ++ " (filter: " ++ Name ++  ")"},
 
908
               {configure, true},
 
909
               {width, S#state.width},
 
910
               {height, S#state.height}],
 
911
    Win     = gs:window(GS, WinOpt),
 
912
    Bar     = gs:menubar(Win, []),
 
913
 
 
914
    create_file_menu(Bar),
 
915
    create_viewer_menu(Bar),
 
916
    create_collector_menu(Bar),
 
917
    gs:menubutton(filter_button, Bar, [{label, {text, "Filter"}}]),
 
918
    create_filter_menu(S#state.active_filter, S#state.filters),
 
919
    create_help_menu(Bar),
 
920
   
 
921
    config_suspend(S),
 
922
 
 
923
    PackerOpt = [{packer_x, [{fixed, 5}, {fixed, 40}, {fixed, 40},
 
924
                             {stretch, 1}, {fixed, 5}]},
 
925
                 {packer_y, [{fixed, 30}, {fixed, 30},
 
926
                             {stretch, 1}, {fixed, 30}]},
 
927
                 {x, 0}, {y, 30}],
 
928
    Packer = gs:frame(Win, PackerOpt),
 
929
    gs:checkbutton(suspended, Packer, [{label,{text,"Freeze"}},
 
930
                                       {x, 10}, {y, 0},
 
931
                                       {width, 120}, {align, w},
 
932
                                       {select, S#state.is_suspended}]),
 
933
    gs:checkbutton(hide_actions, Packer, [{label,{text,"Hide From=To"}},
 
934
                                          {x, 10}, {y, 20},
 
935
                                          {width, 120}, {align, w},
 
936
                                          {select, S#state.hide_actions}]),
 
937
    gs:checkbutton(hide_unknown, Packer, [{label,{text,"Hide Unknown"}},
 
938
                                          {x, 10}, {y, 40},
 
939
                                          {width, 120}, {align, w},
 
940
                                          {select, S#state.hide_unknown}]),
 
941
    gs:scale(Packer, [{text,"Detail Level"},
 
942
                      {range, {?detail_level_min, ?detail_level_max}},
 
943
                      {orient, horizontal},
 
944
                      {x, 150}, {y, 0}, {height, 65}, {width, 200},
 
945
                      {pos, S#state.detail_level}, {data, detail_level}]),
 
946
    CanvasW = calc_canvas_width(S),
 
947
    CanvasH = calc_canvas_height(S),
 
948
    CanOpt = [{pack_xy, {{2, 4}, 3}}, {vscroll, right}, {hscroll, bottom},
 
949
              {scrollregion, {2, 2, CanvasW, CanvasH}}],
 
950
    Canvas = gs:canvas(Packer, CanOpt),
 
951
    gs:config(Canvas, [{buttonpress, true}, {buttonrelease, true}]),
 
952
    gs:config(Packer, [{width, S#state.width}, {height, S#state.height}]),
 
953
    gs:config(Win, [{map, true}, {keypress, true}]),
 
954
    S2 = S#state{title = Title,
 
955
                 win = Win, font = Font, packer = Packer,
 
956
                 canvas_width = CanvasW, canvas_height = CanvasH,
 
957
                 canvas = Canvas,
 
958
                 y_pos = ?initial_y * S#state.scale},
 
959
    draw_all_actors(S2).
 
960
 
 
961
select_font(Scale) when is_integer(Scale) ->
 
962
    case Scale of
 
963
        1 -> {courier,  7};
 
964
        2 -> {courier, 10};
 
965
        3 -> {courier, 12};
 
966
        4 -> {courier, 14};
 
967
        S -> {courier, S * 4}
 
968
    end.
 
969
 
 
970
create_file_menu(Bar) ->
 
971
    Button = gs:menubutton(Bar,  [{label, {text, "File"}}]),
 
972
    Menu   = gs:menu(Button, []),
 
973
    gs:menuitem(close_all, Menu,        [{label, {text, "Close Collector and all Viewers         (C) "}}]),
 
974
    gs:menuitem(close_all_others, Menu, [{label, {text, "Close other Viewers, but keep Collector (c)"}}]),
 
975
    gs:menuitem(close, Menu,            [{label, {text, "Close this  Viewer,  but keep Collector"}}]),
 
976
    gs:menuitem(Menu, [{itemtype, separator}]),
 
977
 
 
978
    gs:menuitem(clear_all, Menu, [{label, {text, "Clear Collector"}}]),
 
979
    gs:menuitem(load_all, Menu,  [{label, {text, "Load  Collector from the file \"et_viewer.log\""}}]),
 
980
    gs:menuitem(save_all, Menu,  [{label, {text, "Save  Collector to   the file \"et_viewer.log\""}}]).
 
981
 
 
982
create_viewer_menu(Bar) ->
 
983
    Button = gs:menubutton(Bar,  [{label, {text, "Viewer"}}]),
 
984
    Menu   = gs:menu(Button, []),
 
985
    gs:menuitem(Menu, [{label, {text, "Scroll this Viewer"}}, {bg, lightblue}, {enable,false}]),
 
986
    gs:menuitem(Menu, [{itemtype, separator}]),
 
987
    gs:menuitem(first, Menu,   [{label, {text, "First                     (f)"}}]),
 
988
    gs:menuitem(prev, Menu,    [{label, {text, "Prev                      (p)"}}]),
 
989
    gs:menuitem(next, Menu,    [{label, {text, "Next                      (n)"}}]),
 
990
    gs:menuitem(last, Menu,    [{label, {text, "Last                      (l)"}}]),
 
991
    gs:menuitem(refresh, Menu, [{label, {text, "Refresh                   (r)"}}]),
 
992
    gs:menuitem(Menu, [{itemtype, separator}]),                  
 
993
    gs:menuitem(up,   Menu,    [{label, {text, "Up   5                    (Up)"}}]),
 
994
    gs:menuitem(down, Menu,    [{label, {text, "Down 5                    (Down)"}}]),
 
995
    gs:menuitem(Menu, [{itemtype, separator}]),
 
996
    gs:menuitem(Menu, [{label, {text, "Search in this Viewer"}}, {bg, lightblue}, {enable,false}]),
 
997
    gs:menuitem(Menu, [{itemtype, separator}]),
 
998
    gs:menuitem({mode, all}, Menu,    [{label, {text, "Abort search. Display all (a)"}}]).
 
999
 
 
1000
create_collector_menu(Bar) ->
 
1001
    Button = gs:menubutton(Bar,  [{label, {text, "Collector"}}]),
 
1002
    Menu = gs:menu(Button, []),
 
1003
    gs:menuitem(Menu, [{label, {text, "Scroll all Viewers"}}, {bg, lightblue}, {enable,false}]),
 
1004
    gs:menuitem(Menu, [{itemtype, separator}]),
 
1005
    gs:menuitem(first_all, Menu,   [{label, {text, "First   (F)"}}]),
 
1006
    gs:menuitem(prev_all, Menu,    [{label, {text, "Prev    (P)"}}]),
 
1007
    gs:menuitem(next_all, Menu,    [{label, {text, "Next    (N)"}}]),
 
1008
    gs:menuitem(last_all, Menu,    [{label, {text, "Last    (L)"}}]),
 
1009
    gs:menuitem(refresh_all, Menu, [{label, {text, "Refresh (R)"}}]).
 
1010
 
 
1011
create_filter_menu(ActiveFilterName, Filters) ->
 
1012
    Menu = gs:menu(filter_menu, filter_button, []),
 
1013
    Item = fun(F, N) when F#filter.name =:= collector ->
 
1014
                   Label = lists:concat([pad_string(F#filter.name, 20), "(0)"]),
 
1015
                   gs:menuitem(Menu, [{label, {text, Label}}, {data, F}]),
 
1016
                   N + 1;
 
1017
              (F, N) ->
 
1018
                   Label = lists:concat([pad_string(F#filter.name, 20), "(", N, ")"]),
 
1019
                   gs:menuitem(Menu, [{label, {text, Label}}, {data, F}]),
 
1020
                   N + 1
 
1021
           end,
 
1022
    gs:menuitem(Menu, [{label, {text, "Same Filter New Scale"}}, {bg, lightblue}, {enable,false}]),
 
1023
    gs:menuitem(Menu, [{itemtype, separator}]),
 
1024
    {value, Filter} = lists:keysearch(ActiveFilterName, #filter.name, Filters),
 
1025
    Same    = lists:concat([pad_string(ActiveFilterName, 20), "(=)"]),
 
1026
    Larger  = lists:concat([pad_string(ActiveFilterName, 20), "(+)"]),
 
1027
    Smaller = lists:concat([pad_string(ActiveFilterName, 20), "(-)"]),
 
1028
    gs:menuitem(Menu, [{label, {text, Same}}, {data, Filter}]),
 
1029
    gs:menuitem(Menu, [{label, {text, Smaller}}, {data, Filter}]),
 
1030
    gs:menuitem(Menu, [{label, {text, Larger}}, {data, Filter}]),
 
1031
    gs:menuitem(Menu, [{itemtype, separator}]),
 
1032
    gs:menuitem(Menu, [{label, {text, "New Filter Same Scale"}}, {bg, lightblue}, {enable,false}]),
 
1033
    gs:menuitem(Menu, [{itemtype, separator}]),
 
1034
    lists:foldl(Item, 1, Filters).
 
1035
 
 
1036
create_help_menu(Bar) ->
 
1037
    Button = gs:menubutton(Bar,  [{label, {text, "Help"}}]),
 
1038
    Menu = gs:menu(Button, []),
 
1039
    gs:menuitem(Menu, [{label, {text, "Display details of an event"}},
 
1040
                       {bg, lightblue}, {enable,false}]),
 
1041
    gs:menuitem(Menu, [{label, {text, "    Single click on the name tag or the arrow (Mouse-1)"}},
 
1042
                       {enable,false}]),
 
1043
    gs:menuitem(Menu, [{itemtype, separator}]),
 
1044
    gs:menuitem(Menu, [{label, {text, "Toggle actor search"}},
 
1045
                       {bg, lightblue}, {enable,false}]),
 
1046
    gs:menuitem(Menu, [{label, {text, "    Single click on the name tag (Mouse-1)"}},
 
1047
                       {enable,false}]),
 
1048
    gs:menuitem(Menu, [{itemtype, separator}]),
 
1049
    gs:menuitem(Menu, [{label, {text, "Move actor"}},
 
1050
                       {bg, lightblue}, {enable,false}]),
 
1051
    gs:menuitem(Menu, [{label, {text, "    se drag and drop on name tag (Mouse-1)"}},
 
1052
                       {enable,false}]).
 
1053
 
 
1054
clear_canvas(S) ->
 
1055
    gs:destroy(S#state.canvas),
 
1056
    CanvasW = calc_canvas_width(S),
 
1057
    CanvasH = calc_canvas_height(S),
 
1058
    CanOpt = [{pack_xy, {{2, 4}, 3}}, {vscroll, right}, {hscroll, bottom},
 
1059
              {scrollregion, {2, 2, CanvasW, CanvasH}}],
 
1060
    Canvas = gs:canvas(S#state.packer, CanOpt),
 
1061
    gs:config(S#state.packer, [{width, S#state.width}, {height, S#state.height}]), 
 
1062
    gs:config(Canvas, [{buttonpress, true}, {buttonrelease, true}]),
 
1063
    S2 = S#state{refresh_needed = false,
 
1064
                 y_pos          = ?initial_y * S#state.scale,
 
1065
                 canvas         = Canvas,
 
1066
                 canvas_width   = CanvasW, 
 
1067
                 canvas_height  = CanvasH,
 
1068
                 events         = queue_new()},
 
1069
    draw_all_actors(S2).
 
1070
 
 
1071
calc_canvas_width(S) ->
 
1072
    Min = calc_min_actors(S),
 
1073
    CanvasW = ((2 * ?initial_x) + (Min * ?incr_x)) * S#state.scale,
 
1074
    lists:max([CanvasW, S#state.width - (15 * S#state.scale), S#state.canvas_width]).
 
1075
 
 
1076
calc_canvas_height(S) ->
 
1077
    Min = calc_min_events(S),
 
1078
    CanvasH = ((2 * ?initial_y) + (Min * ?incr_y)) * S#state.scale,
 
1079
    lists:max([CanvasH, S#state.height - (4 * 30), S#state.canvas_height]).
 
1080
 
 
1081
calc_min_actors(S) ->
 
1082
    Max = S#state.max_actors,
 
1083
    N   = length(S#state.actors),
 
1084
    if
 
1085
        Max =:= infinity ->
 
1086
            N * 2;
 
1087
        Max < N ->
 
1088
            N;
 
1089
        true ->
 
1090
            Max
 
1091
    end.
 
1092
    
 
1093
calc_min_events(S) ->
 
1094
    Max = S#state.max_events,
 
1095
    N   = queue_length(S#state.events),
 
1096
    if
 
1097
        Max =:= infinity ->
 
1098
            N * 2;
 
1099
        Max < N ->
 
1100
            N;
 
1101
        true ->
 
1102
            Max
 
1103
    end.
 
1104
 
 
1105
display_more_events(Try, S) ->
 
1106
    Name = S#state.active_filter,
 
1107
    {value, F} = lists:keysearch(Name, #filter.name, S#state.filters),
 
1108
    FilterFun = F#filter.function,
 
1109
    Fun = fun(Event, State) ->
 
1110
              case catch FilterFun(Event) of
 
1111
                  true ->
 
1112
                      State2 = ensure_key(Event, State),
 
1113
                      opt_display_event(Event, State2);
 
1114
                  {true, Event2} -> 
 
1115
                      State2 = ensure_key(Event2, State),
 
1116
                      opt_display_event(Event2, State2);
 
1117
                  false ->
 
1118
                      ensure_key(Event, State);
 
1119
                  Bad ->
 
1120
                      Contents = {bad_filter, Name, Bad, Event},
 
1121
                      Event2 = Event#event{contents = Contents,
 
1122
                                           from     = bad_filter,
 
1123
                                           to       = bad_filter},
 
1124
                      State2 = ensure_key(Event2, State),
 
1125
                      opt_display_event(Event2, State2)
 
1126
              end
 
1127
          end,
 
1128
    Pid = S#state.collector_pid,
 
1129
    S2 = et_collector:iterate(Pid, S#state.last_event, Try, Fun, S),
 
1130
    case queue_length(S2#state.events) - queue_length(S#state.events) of
 
1131
        Diff when Diff =:= Try ->
 
1132
            %% Got as much as requested, look for more
 
1133
            %% io:format("Done: ~p~n", [{Try, Diff}]),
 
1134
            {noreply, S2, 0};
 
1135
        _Diff when S2#state.first_event =:= S#state.first_event,
 
1136
                  S2#state.last_event  =:= S#state.last_event ->
 
1137
            %% Got lesser than requested, wait a while before looking for more
 
1138
            %% io:format("More: ~p~n", [{Try, Diff}]),
 
1139
            {noreply, S2, 500};
 
1140
        _Diff ->
 
1141
            %% Got lesser than requested, look for more
 
1142
            %% io:format("More2: ~p~n", [{Try, Diff}]),
 
1143
            {noreply, S2, 0}
 
1144
    end.
 
1145
 
 
1146
ensure_key(E, S) when is_record(E, event), is_record(S, state)  ->
 
1147
    Key  = et_collector:make_key(S#state.event_order, E),
 
1148
    case S#state.first_event of
 
1149
             first ->
 
1150
                 S#state{first_event = Key, last_event = Key};
 
1151
             last ->
 
1152
                 S#state{first_event = Key, last_event = Key};
 
1153
             _     -> 
 
1154
                 S#state{last_event = Key}
 
1155
    end.
 
1156
 
 
1157
opt_display_event(E, S) ->
 
1158
    case S#state.display_mode of
 
1159
        all ->
 
1160
            display_event(E, S);
 
1161
        {search_actors, _Dir, _FirstKey, Actors} ->
 
1162
            %% Key = S#state.last_event,
 
1163
            From = select_actor_name(E#event.from, S),
 
1164
            case lists:member(From, Actors) of
 
1165
                true ->
 
1166
                    display_event(E, S);
 
1167
                false ->
 
1168
                    To = select_actor_name(E#event.to, S),
 
1169
                    case lists:member(To, Actors) of
 
1170
                        true ->
 
1171
                            display_event(E, S);
 
1172
                        false ->
 
1173
                            S
 
1174
                    end
 
1175
            end
 
1176
    end.
 
1177
 
 
1178
select_actor_name(Name, S) ->
 
1179
    case lists:keymember(Name, #actor.name, S#state.actors) of
 
1180
        true  ->  Name;
 
1181
        false ->  ?unknown
 
1182
    end.
 
1183
 
 
1184
display_event(E, S) when E#event.detail_level < S#state.detail_level ->
 
1185
    {FromRefresh, From} = ensure_actor(E#event.from, S),
 
1186
    {FromName, FromPos, S2} = From,
 
1187
    {ToRefresh, To} = ensure_actor(E#event.to, S2),
 
1188
    {ToName, ToPos, S3} = To,
 
1189
    if
 
1190
        FromRefresh =/= false, ToRefresh =/= false ->
 
1191
            Key = S#state.last_event,
 
1192
            refresh_beep(S),
 
1193
            S3#state{refresh_needed = true,
 
1194
                     events = queue_in(Key, S3#state.events)};
 
1195
        FromName =:= ToName ->
 
1196
            case S#state.hide_actions of
 
1197
                true  -> 
 
1198
                    S3;
 
1199
                false -> 
 
1200
                    Label = name_to_string(E#event.label),
 
1201
                    draw_named_arrow(Label, FromName, FromPos, ToName, ToPos, S3)
 
1202
            end;
 
1203
        true ->
 
1204
            Label = name_to_string(E#event.label),
 
1205
            draw_named_arrow(Label, FromName, FromPos, ToName, ToPos, S3)
 
1206
    end;
 
1207
display_event(_, S) ->
 
1208
    S.
 
1209
 
 
1210
draw_named_arrow(Label, FromName, FromPos, ToName, ToPos, S) ->
 
1211
    Key = S#state.last_event,
 
1212
    case S#state.y_pos + (?incr_y *  S#state.scale) of
 
1213
        _ when S#state.hide_unknown =:= true, FromName =:= ?unknown ->
 
1214
            S;
 
1215
        _ when S#state.hide_unknown =:= true, ToName =:= ?unknown ->
 
1216
            S;
 
1217
        Y when  Y > S#state.canvas_height ->
 
1218
            refresh_beep(S),
 
1219
            S#state{refresh_needed = true,
 
1220
                    events = queue_in(Key, S#state.events)};
 
1221
        Y ->
 
1222
            S2 = S#state{y_pos  = Y, events = queue_in(Key, S#state.events)},
 
1223
            S3 = draw_arrow(FromPos, ToPos, S2),
 
1224
            draw_label(Label, FromName, ToName, FromPos, ToPos, S3)
 
1225
    end.
 
1226
 
 
1227
refresh_beep(S) ->
 
1228
    case S#state.refresh_needed of
 
1229
        false  -> 
 
1230
            gs:config(S#state.canvas, beep),
 
1231
            gs:config(S#state.canvas, beep),
 
1232
            gs:config(S#state.canvas, beep);
 
1233
        true -> 
 
1234
            ignore
 
1235
    end.
 
1236
 
 
1237
draw_arrow(Pos, Pos, S) ->
 
1238
    S;
 
1239
draw_arrow(FromPos, ToPos, S) ->
 
1240
    Y = S#state.y_pos,
 
1241
    CanOpts = [{coords, [{FromPos , Y}, {ToPos, Y}]},
 
1242
               {arrow, last},{width, 1}, {fg, black}],
 
1243
    gs:line(S#state.canvas, CanOpts),
 
1244
    S.
 
1245
 
 
1246
draw_label(Label, FromName, ToName, FromPos, ToPos, S) ->
 
1247
    Colour =
 
1248
        if
 
1249
            FromName =:= ?unknown, 
 
1250
            ToName   =:= ?unknown -> blue; %turquoise;
 
1251
            FromName =:= ?unknown -> orange;
 
1252
            ToName   =:= ?unknown -> orange;
 
1253
            FromPos  =:= ToPos    -> blue;
 
1254
            true                  -> red
 
1255
        end,
 
1256
    Scale = S#state.scale,
 
1257
    X = lists:min([FromPos, ToPos]) + (6 * Scale),
 
1258
    Y = S#state.y_pos,
 
1259
    write_text(Label, X, Y, Colour, S),
 
1260
    S.
 
1261
 
 
1262
draw_all_actors(State) ->
 
1263
    Scale = State#state.scale,
 
1264
    Fun = fun(A, X) ->
 
1265
                  draw_actor(A, X, State),
 
1266
                  X + (?incr_x * Scale)
 
1267
          end,
 
1268
    lists:foldl(Fun, ?initial_x * Scale, State#state.actors),
 
1269
    State.
 
1270
 
 
1271
%% Returns: {NeedsRefreshBool, {ActorPos, NewsS, NewActors}}
 
1272
ensure_actor(Name, S) ->
 
1273
    do_ensure_actor(Name, S, S#state.actors, 0).
 
1274
 
 
1275
do_ensure_actor(Name, S, [H | _], N) when H#actor.name =:= Name ->
 
1276
    Pos = (?initial_x + (N * ?incr_x)) * S#state.scale,
 
1277
    {false, {Name, Pos, S}};
 
1278
do_ensure_actor(Name, S, [_ | T], N) ->
 
1279
    do_ensure_actor(Name, S, T, N + 1);
 
1280
do_ensure_actor(Name, S, [], N) ->
 
1281
    %% A brand new actor, let's see if it does fit
 
1282
    Pos = (?initial_x + (N * ?incr_x)) * S#state.scale,
 
1283
    MaxActors = S#state.max_actors,
 
1284
    if
 
1285
        is_integer(MaxActors), N > MaxActors ->
 
1286
            %% Failed on max_actors limit, put into unknown
 
1287
            %% Assume that unknown always is in actor list
 
1288
            ensure_actor(?unknown, S);
 
1289
        Pos > (S#state.canvas_width - ((?initial_x - 15) * S#state.scale)) ->
 
1290
            %% New actor does not fit in canvas, refresh needed
 
1291
            A = create_actor(Name),
 
1292
            draw_actor(A, Pos, S),
 
1293
            {true, {Name, Pos, S#state{actors = S#state.actors ++ [A]}}};
 
1294
        true ->
 
1295
            %% New actor fits in canvas. Draw the new actor.
 
1296
            A = create_actor(Name),
 
1297
            draw_actor(A, Pos, S),
 
1298
            {false, {Name, Pos, S#state{actors = S#state.actors ++ [A]}}}
 
1299
    end.
 
1300
 
 
1301
draw_actor(A, LineX, S) ->
 
1302
    Scale    = S#state.scale,
 
1303
    TextX    = LineX - (5 * Scale),
 
1304
    TextY    = ?initial_y * Scale,
 
1305
    LineTopY = TextY + ((?incr_y  / 2) * Scale),
 
1306
    LineBotY = S#state.canvas_height - ((?incr_y / 2) * Scale),
 
1307
    Colour   = case A#actor.name of
 
1308
                   ?unknown -> orange;
 
1309
                   _        -> red
 
1310
               end,
 
1311
    write_text(A#actor.string, TextX, TextY, Colour, S),
 
1312
    LineOpt = [{coords, [{LineX, LineTopY}, {LineX, LineBotY}]},
 
1313
               {width, 1}, {fg, Colour}],
 
1314
    gs:line(S#state.canvas, LineOpt).
 
1315
 
 
1316
toggle_search_for_actor(ActorName,S) ->    
 
1317
    case S#state.display_mode of
 
1318
        all ->
 
1319
            io:format("~p: search for: ~p ++ ~p~n", [?MODULE, [], [ActorName]]),
 
1320
            %% Search for this actor
 
1321
            Key = S#state.first_event,
 
1322
            Actors = [ActorName],
 
1323
            Mode = {search_actors, forward, Key, Actors},
 
1324
            change_display_mode(Mode, S);
 
1325
        {search_actors, Dir, Key, Actors}->
 
1326
            Actors2 = 
 
1327
                case lists:member(ActorName, Actors) of
 
1328
                    true ->
 
1329
                        io:format("~p: search for: ~p -- ~p~n", [?MODULE, Actors, [ActorName]]),
 
1330
                        %% Remove actor from search list
 
1331
                        Actors -- [ActorName];
 
1332
                    false ->
 
1333
                        io:format("~p: search for: ~p ++ ~p~n", [?MODULE, Actors, [ActorName]]),
 
1334
                        %% Add actor from search list
 
1335
                        [ActorName | Actors]
 
1336
                end,
 
1337
            Mode2 = {search_actors, Dir, Key, Actors2},
 
1338
            change_display_mode(Mode2, S)
 
1339
    end.
 
1340
 
 
1341
move_actor(From, To, Actors, S) ->
 
1342
    Pos      = #actor.name,
 
1343
    ToName   = To#actor.name,
 
1344
    FromName = From#actor.name,
 
1345
    ToIx     = actor_index(ToName, Pos, Actors),
 
1346
    FromIx   = actor_index(FromName, Pos, Actors),
 
1347
    if
 
1348
        FromIx =/= 0, ToIx =/= 0, ToIx > FromIx ->
 
1349
            Actors2 = lists:keydelete(FromName, Pos, Actors),
 
1350
            Actors3 = insert_actor_after(From, To, Actors2),
 
1351
            S2 = S#state{actors = Actors3},
 
1352
            refresh_main_window(S2);
 
1353
        FromIx =/= 0, ToIx =/= 0 ->
 
1354
            Actors2 = lists:keydelete(FromName, Pos, Actors),
 
1355
            Actors3 = insert_actor_before(From, To, Actors2),
 
1356
            S2 = S#state{actors = Actors3},
 
1357
            refresh_main_window(S2);
 
1358
        true ->
 
1359
            %% Ignore
 
1360
            S
 
1361
    end.
 
1362
 
 
1363
insert_actor_after(From, To, [H | T]) ->
 
1364
    case To#actor.name =:= H#actor.name of
 
1365
        true  -> [H, From | T];
 
1366
        false -> [H | insert_actor_after(From, To, T)]
 
1367
    end;
 
1368
insert_actor_after(_From, _To, []) ->
 
1369
    [].
 
1370
 
 
1371
insert_actor_before(From, To, [H | T]) ->
 
1372
    case To#actor.name =:= H#actor.name of
 
1373
        true  -> [From, H | T];
 
1374
        false -> [H | insert_actor_before(From, To, T)]
 
1375
    end;
 
1376
insert_actor_before(_From, _To, []) ->
 
1377
    [].
 
1378
 
 
1379
actor_index(_Key, _Pos, []) ->
 
1380
    0;
 
1381
actor_index(Key, Pos, [H | T]) ->
 
1382
    case Key =:= element(Pos, H) of
 
1383
        false -> actor_index(Key, Pos, T) + 1;
 
1384
        true  -> 1
 
1385
    end.
 
1386
 
 
1387
y_to_n(Y, S) ->
 
1388
    Y2   = ((Y / S#state.scale) - ?initial_y + (?incr_y / 2)),
 
1389
    N    = round(Y2 / ?incr_y - 0.2),
 
1390
    MaxN = queue_length(S#state.events),
 
1391
    if
 
1392
        N =< 0   -> actor;
 
1393
        N > MaxN -> actor;
 
1394
        true     -> {event, N}
 
1395
    end.
 
1396
 
 
1397
x_to_n(X, S) ->
 
1398
    Scale   = S#state.scale,
 
1399
    Len = length(S#state.actors),
 
1400
    X2 = X - (?initial_x * Scale),
 
1401
    N  = X2 / (?incr_x * Scale),
 
1402
    N2 = trunc(N + 1.5),
 
1403
    if
 
1404
        N2 > Len -> Len;
 
1405
        N2 < 1   -> 1;
 
1406
        true     -> N2
 
1407
    end.
 
1408
 
 
1409
write_text(Text, X, Y, Colour, S) ->
 
1410
    Opt = [{coords, [{X, Y - (?incr_y * S#state.scale / 2)}]},
 
1411
           {font, S#state.font}, {fg, Colour}, {text, Text}],
 
1412
    gs:text(S#state.canvas, Opt).
 
1413
 
 
1414
create_contents_window(Event, S) ->
 
1415
    Options = [{viewer_pid, self()},
 
1416
               {event, Event},
 
1417
               {event_order, S#state.event_order},
 
1418
               {active_filter, S#state.active_filter}
 
1419
               | S#state.filters],
 
1420
    case et_gs_contents_viewer:start_link(Options) of
 
1421
        {ok, _Pid} ->
 
1422
            S;
 
1423
        {error, Reason} ->
 
1424
            ok = error_logger:format("~p(~p): create_contents_window(~p) ->~n     ~p~n",
 
1425
                                     [?MODULE, self(), Options, Reason]),
 
1426
            S
 
1427
    end.
 
1428
 
 
1429
%%%----------------------------------------------------------------------
 
1430
%%% String padding of actors
 
1431
%%%----------------------------------------------------------------------
 
1432
 
 
1433
create_actor(Name) ->
 
1434
    String = name_to_string(Name),
 
1435
    PaddedString = pad_string(String, 8),
 
1436
    #actor{name = Name, string = PaddedString}.
 
1437
 
 
1438
name_to_string(Name) ->
 
1439
    case catch io_lib:format("~s", [Name]) of
 
1440
        {'EXIT', _} -> lists:flatten(io_lib:format("~w", [Name]));
 
1441
        GoodString  -> lists:flatten(GoodString)
 
1442
    end.
 
1443
 
 
1444
pad_string(Atom, MinLen) when is_atom(Atom) ->
 
1445
    pad_string(atom_to_list(Atom), MinLen);
 
1446
pad_string(String, MinLen) when is_integer(MinLen), MinLen >= 0 ->
 
1447
    Len = length(String),
 
1448
    case Len >= MinLen of
 
1449
        true ->
 
1450
            String;
 
1451
        false ->
 
1452
            String ++ lists:duplicate(MinLen - Len, $ )
 
1453
    end.
 
1454
 
 
1455
%%%----------------------------------------------------------------------
 
1456
%%% Queue management
 
1457
%%%----------------------------------------------------------------------
 
1458
 
 
1459
queue_new() ->
 
1460
    {0, [], []}.
 
1461
 
 
1462
queue_in(X, {Size, In, Out}) ->
 
1463
    {Size + 1, [X | In], Out}.
 
1464
 
 
1465
%% queue_out(Q) ->
 
1466
%%     case Q of
 
1467
%%         {Size, In, [H | Out]} -> {{value, H}, {Size - 1, In, Out}};
 
1468
%%         {Size, [], []}        -> {empty, {Size, [], []}};
 
1469
%%         {Size, In, _}         -> queue_out({Size, [], lists:reverse(In)})
 
1470
%%     end.
 
1471
 
 
1472
queue_to_list({_Size, [], Out}) ->
 
1473
    Out;
 
1474
queue_to_list({_Size, In, Out}) ->
 
1475
    Out ++ lists:reverse(In).
 
1476
 
 
1477
queue_length({Size, _In, _Out}) ->
 
1478
    Size.
 
1479
 
 
1480
list_to_queue(List) when is_list(List) ->
 
1481
    {length(List), [], List}.