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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2000-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 details of a trace event
 
21
%%----------------------------------------------------------------------
 
22
 
 
23
-module(et_gs_contents_viewer).
 
24
 
 
25
-behaviour(gen_server).
 
26
 
 
27
%% External exports
 
28
-export([start_link/1, 
 
29
         stop/1]).
 
30
 
 
31
%% gen_server callbacks
 
32
-export([init/1, terminate/2, code_change/3,
 
33
         handle_call/3, handle_cast/2, handle_info/2]).
 
34
 
 
35
-include("../include/et.hrl").
 
36
-include("et_internal.hrl").
 
37
 
 
38
-record(state, {parent_pid,     % Pid of parent process
 
39
                viewer_pid,     % Pid of viewer process
 
40
                event_order,    % Field to be used as primary key
 
41
                event,          % The original event
 
42
                filtered_event, % Event processed by active filter
 
43
                active_filter,  % Name of the active filter
 
44
                filters,        % List of possible filters
 
45
                win,            % GUI: Window object
 
46
                packer,         % GUI: Packer object
 
47
                width,          % GUI: Window width
 
48
                height}).       % GUI: Window height
 
49
 
 
50
%%%----------------------------------------------------------------------
 
51
%%% Client side
 
52
%%%----------------------------------------------------------------------
 
53
 
 
54
%%----------------------------------------------------------------------
 
55
%% start_link(Options) -> {ok, ContentsPid} | {error, Reason}
 
56
%%
 
57
%% Start an viewer for the event contents as window in GS
 
58
%%
 
59
%% Options = [option()]
 
60
%% 
 
61
%% option() =
 
62
%% 
 
63
%%   {parent_pid, pid()}          |  % Pid of parent process
 
64
%%   {viewer_pid, pid()}          |  % Pid of viewer process
 
65
%%   {event_order, event_order()} |  % Field to be used as primary key 
 
66
%%   {active_filter, atom()}      |  % Name of the active filter
 
67
%%   {filter, atom(), fun()}         % A named filter fun
 
68
%%   
 
69
%% event_order() = 'trace_ts' | 'event_ts'
 
70
%% ContentsPid = pid()
 
71
%% Reason = term()
 
72
%%----------------------------------------------------------------------
 
73
 
 
74
start_link(Options) ->
 
75
    case parse_opt(Options, default_state()) of
 
76
        {ok, S} ->
 
77
            case gen_server:start_link(?MODULE, [S], []) of
 
78
                {ok, ContentsPid} when S#state.parent_pid =/= self() ->
 
79
                    unlink(ContentsPid),
 
80
                    {ok, ContentsPid};
 
81
                Other ->
 
82
                    Other
 
83
            end;
 
84
        {error, Reason} ->
 
85
            {error, Reason}
 
86
    end.
 
87
 
 
88
default_state() ->
 
89
    #state{parent_pid    = self(),
 
90
           viewer_pid    = undefined,
 
91
           active_filter = ?DEFAULT_FILTER_NAME,
 
92
           filters       = [?DEFAULT_FILTER],
 
93
           width         = 600,
 
94
           height        = 300}.
 
95
 
 
96
parse_opt([], S) ->
 
97
    Name = S#state.active_filter,
 
98
    Filters = S#state.filters,
 
99
    if
 
100
        S#state.event =:= undefined ->
 
101
            {error, {badarg, no_event}};
 
102
        is_atom(Name) ->
 
103
            case lists:keysearch(Name, #filter.name, Filters) of
 
104
                {value, F} when is_record(F, filter) ->
 
105
                    {ok, S#state{active_filter = Name}};
 
106
                false ->
 
107
                    {error, {badarg, {no_such_filter, Name, Filters}}}
 
108
            end
 
109
    end;
 
110
parse_opt([H | T], S) ->
 
111
    case H of
 
112
        {parent_pid, ParentPid} when is_pid(ParentPid) ->
 
113
            parse_opt(T, S#state{parent_pid = ParentPid});
 
114
        {viewer_pid, ViewerPid} when is_pid(ViewerPid) ->
 
115
            parse_opt(T, S#state{viewer_pid = ViewerPid});
 
116
        {event_order, trace_ts} ->
 
117
            parse_opt(T, S#state{event_order = trace_ts});
 
118
        {event_order, event_ts} ->
 
119
            parse_opt(T, S#state{event_order = event_ts});
 
120
        {event, Event} when is_record(Event, event) ->
 
121
            parse_opt(T, S#state{event = Event});
 
122
        {active_filter, Name} when is_atom(Name) ->
 
123
            parse_opt(T, S#state{active_filter = Name});
 
124
        F when is_record(F, filter),
 
125
               is_atom(F#filter.name),
 
126
               is_function(F#filter.function) ->
 
127
            Filters = lists:keydelete(F#filter.name, #filter.name, S#state.filters),
 
128
            Filters2 = lists:keysort(#filter.name, [F | Filters]),
 
129
            parse_opt(T, S#state{filters = Filters2});
 
130
        {width, Width} when is_integer(Width), Width > 0 ->
 
131
            parse_opt(T, S#state{width = Width});
 
132
        {height, Height} when is_integer(Height), Height > 0 ->
 
133
            parse_opt(T, S#state{height = Height});
 
134
        Bad ->
 
135
            {error, {bad_option, Bad}}
 
136
    end;
 
137
parse_opt(BadList, _S) ->
 
138
    {error, {bad_option_list, BadList}}.
 
139
 
 
140
%%----------------------------------------------------------------------
 
141
%% stop(ContentsPid) -> ok
 
142
%%
 
143
%% Stops a contents viewer process
 
144
%%
 
145
%% ContentsPid = pid()
 
146
%%----------------------------------------------------------------------
 
147
 
 
148
stop(ContentsPid) ->
 
149
    unlink(ContentsPid),
 
150
    call(ContentsPid, stop).
 
151
 
 
152
call(ContentsPid, Request) ->
 
153
    gen_server:call(ContentsPid, Request, infinity).
 
154
 
 
155
%%%----------------------------------------------------------------------
 
156
%%% Callback functions from gen_server
 
157
%%%----------------------------------------------------------------------
 
158
 
 
159
%%----------------------------------------------------------------------
 
160
%% Func: init/1
 
161
%% Returns: {ok, State}          |
 
162
%%          {ok, State, Timeout} |
 
163
%%          ignore               |
 
164
%%          {stop, Reason}
 
165
%%----------------------------------------------------------------------
 
166
 
 
167
init([S]) when is_record(S, state) ->
 
168
    process_flag(trap_exit, true),
 
169
    S2 = create_window(S),
 
170
    {ok, S2}.
 
171
 
 
172
%%----------------------------------------------------------------------
 
173
%% Func: handle_call/3
 
174
%% Returns: {reply, Reply, State}          |
 
175
%%          {reply, Reply, State, Timeout} |
 
176
%%          {noreply, State}               |
 
177
%%          {noreply, State, Timeout}      |
 
178
%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
 
179
%%          {stop, Reason, State}            (terminate/2 is called)
 
180
%%----------------------------------------------------------------------
 
181
 
 
182
handle_call(stop, _From, S) ->
 
183
    unlink(S#state.parent_pid),
 
184
    {stop, shutdown, ok, S};
 
185
handle_call(Request, From, S) ->
 
186
    ok = error_logger:format("~p(~p): handle_call(~p, ~p, ~p)~n",
 
187
                             [?MODULE, self(), Request, From, S]),
 
188
    Reply = {error, {bad_request, Request}},
 
189
    {reply, Reply, S}.
 
190
 
 
191
%%----------------------------------------------------------------------
 
192
%% Func: handle_cast/2
 
193
%% Returns: {noreply, State}          |
 
194
%%          {noreply, State, Timeout} |
 
195
%%          {stop, Reason, State}            (terminate/2 is called)
 
196
%%----------------------------------------------------------------------
 
197
 
 
198
handle_cast(Msg, S) ->
 
199
    ok = error_logger:format("~p(~p): handle_cast(~p, ~p)~n",
 
200
                             [?MODULE, self(), Msg, S]),
 
201
    {noreply, S}.
 
202
 
 
203
%%----------------------------------------------------------------------
 
204
%% Func: handle_info/2
 
205
%% Returns: {noreply, State}          |
 
206
%%          {noreply, State, Timeout} |
 
207
%%          {stop, Reason, State}            (terminate/2 is called)
 
208
%%----------------------------------------------------------------------
 
209
 
 
210
handle_info({gs, Button, click, Data, _Other}, S) ->
 
211
    case Button of
 
212
        close ->
 
213
            gs:destroy(S#state.win),
 
214
            {stop, normal, S};
 
215
        save ->
 
216
            Event = S#state.event,
 
217
            Bin = list_to_binary(event_to_string(Event, S#state.event_order)),
 
218
            TimeStamp = 
 
219
                case S#state.event_order of
 
220
                    trace_ts -> Event#event.trace_ts;
 
221
                    event_ts   -> Event#event.event_ts
 
222
                end,
 
223
            FileName = ["et_contents_viewer_", now_to_string(TimeStamp), ".save"],
 
224
            file:write_file(lists:flatten(FileName), Bin),
 
225
            {noreply, S};
 
226
        _PopupMenuItem when is_record(Data, filter) ->
 
227
            F = Data,
 
228
            ChildState= S#state{active_filter = F#filter.name},
 
229
            case gen_server:start_link(?MODULE, [ChildState], []) of
 
230
                {ok, Pid} when S#state.parent_pid =/= self() ->
 
231
                    unlink(Pid),
 
232
                    {noreply, S};
 
233
                _ ->
 
234
                    {noreply, S}
 
235
            end;
 
236
        {hide, Actors} ->
 
237
            send_viewer_event(S, {delete_actors, Actors}),
 
238
            {noreply, S};
 
239
        {show, Actors} ->
 
240
            send_viewer_event(S, {insert_actors, Actors}),
 
241
            {noreply, S};
 
242
        {mode, Mode} ->
 
243
            send_viewer_event(S, {mode, Mode}),
 
244
            {noreply, S};
 
245
        Nyi ->
 
246
            ok = error_logger:format("~p: click ~p ignored (nyi)~n",
 
247
                                     [?MODULE, Nyi]),
 
248
            {noreply, S}
 
249
    end;
 
250
handle_info({gs, _Obj, destroy,_, _}, S) ->
 
251
    unlink(S#state.parent_pid),
 
252
    gs:destroy(S#state.win),
 
253
    {stop, normal, S};
 
254
handle_info({gs, _Obj, keypress, _, [KeySym, _Keycode, _Shift, _Control | _]}, S) ->
 
255
    case KeySym of
 
256
        'c' ->
 
257
            gs:destroy(S#state.win),
 
258
            {stop, normal, S};
 
259
 
 
260
        'f' ->
 
261
            E    = S#state.filtered_event,
 
262
            From = E#event.from,
 
263
            send_viewer_event(S, {delete_actors, [From]}),
 
264
            {noreply, S};
 
265
        't' ->
 
266
            E  = S#state.filtered_event,
 
267
            To = E#event.to,
 
268
            send_viewer_event(S, {delete_actors, [To]}),
 
269
            {noreply, S};
 
270
        'b' ->
 
271
            E    = S#state.filtered_event,
 
272
            From = E#event.from,
 
273
            To   = E#event.to,
 
274
            send_viewer_event(S, {delete_actors, [From, To]}),
 
275
            {noreply, S};
 
276
        
 
277
        'F' ->
 
278
            E    = S#state.filtered_event,
 
279
            From = E#event.from,
 
280
            send_viewer_event(S, {insert_actors, [From]}),
 
281
            {noreply, S};
 
282
        'T' ->
 
283
            E  = S#state.filtered_event,
 
284
            To = E#event.to,
 
285
            send_viewer_event(S, {insert_actors, [To]}),
 
286
            {noreply, S};
 
287
        'B' ->
 
288
            E    = S#state.filtered_event,
 
289
            From = E#event.from,
 
290
            To   = E#event.to,
 
291
            send_viewer_event(S, {insert_actors, [From, To]}),
 
292
            {noreply, S};
 
293
 
 
294
        's' ->
 
295
            E     = S#state.filtered_event,
 
296
            From  = E#event.from,
 
297
            To    = E#event.to,
 
298
            First = et_collector:make_key(S#state.event_order, E),
 
299
            Mode  = {search_actors, forward, First, [From, To]},
 
300
            send_viewer_event(S, {mode, Mode}),
 
301
            {noreply, S};
 
302
        'r' ->
 
303
            E     = S#state.filtered_event,
 
304
            From  = E#event.from,
 
305
            To    = E#event.to,
 
306
            First = et_collector:make_key(S#state.event_order, E),
 
307
            Mode  = {search_actors, reverse, First, [From, To]},
 
308
            send_viewer_event(S, {mode, Mode}),
 
309
            {noreply, S};
 
310
        'a' ->
 
311
            send_viewer_event(S, {mode, all}),
 
312
            {noreply, S};
 
313
 
 
314
        0 ->
 
315
            case lists:keysearch(?DEFAULT_FILTER_NAME, #filter.name, S#state.filters) of
 
316
                {value, F} when is_record(F, filter) ->
 
317
                    ChildState= S#state{active_filter = F#filter.name},
 
318
                    case gen_server:start_link(?MODULE, [ChildState], []) of
 
319
                        {ok, Pid} when S#state.parent_pid =/= self() ->
 
320
                            unlink(Pid);
 
321
                        _ ->
 
322
                            ignore
 
323
                    end;
 
324
                false ->
 
325
                    ignore
 
326
            end,
 
327
            {noreply, S};
 
328
        Int when is_integer(Int), Int > 0, Int =< 9 ->
 
329
            case catch lists:nth(Int, S#state.filters) of
 
330
                F when is_record(F, filter) ->
 
331
                    ChildState= S#state{active_filter = F#filter.name},
 
332
                    case gen_server:start_link(?MODULE, [ChildState], []) of
 
333
                        {ok, Pid} when S#state.parent_pid =/= self() ->
 
334
                            unlink(Pid);
 
335
                        _ ->
 
336
                            ignore
 
337
                    end;
 
338
                {'EXIT', _} ->
 
339
                    ignore
 
340
            end,
 
341
            {noreply, S};
 
342
 
 
343
        'Shift_L' ->
 
344
            {noreply, S};
 
345
        'Shift_R' ->
 
346
            {noreply, S};
 
347
        'Caps_Lock' ->
 
348
            {noreply, S};
 
349
        _ ->
 
350
            io:format("~p: ignored: ~p~n", [?MODULE, KeySym]),
 
351
            {noreply, S}
 
352
    end;
 
353
handle_info({gs, _Obj, configure, [], [W, H | _]}, S) ->
 
354
    gs:config(S#state.packer, [{width, W},{height, H}]),
 
355
    S2 = S#state{width = W, height = H},
 
356
    {noreply, S2};
 
357
handle_info({'EXIT', Pid, Reason}, S) ->
 
358
    if
 
359
        Pid =:= S#state.parent_pid ->
 
360
            unlink(Pid),
 
361
            {stop, Reason, S};
 
362
        true ->
 
363
            {noreply, S}
 
364
    end;
 
365
handle_info(Info, S) ->
 
366
    ok = error_logger:format("~p(~p): handle_info(~p, ~p)~n",
 
367
                             [?MODULE, self(), Info, S]),
 
368
    {noreply, S}.
 
369
 
 
370
%%----------------------------------------------------------------------
 
371
%% Func: terminate/2
 
372
%% Purpose: Shutdown the server
 
373
%% Returns: any (ignored by gen_server)
 
374
%%----------------------------------------------------------------------
 
375
 
 
376
terminate(_Reason, _S) ->
 
377
    ignore.
 
378
 
 
379
%%----------------------------------------------------------------------
 
380
%% Func: code_change/3
 
381
%% Purpose: Convert process state when code is changed
 
382
%% Returns: {ok, NewState}
 
383
%%----------------------------------------------------------------------
 
384
 
 
385
code_change(_OldVsn, S, _Extra) ->
 
386
    {ok, S}.
 
387
 
 
388
%%%----------------------------------------------------------------------
 
389
%%% Handle graphics
 
390
%%%----------------------------------------------------------------------
 
391
 
 
392
create_window(S) ->
 
393
    H = S#state.height,
 
394
    W = S#state.width,
 
395
    Name = S#state.active_filter,
 
396
    Title = lists:concat([?MODULE, " (filter: ", Name, ")"]),
 
397
    WinOpt = [{title, Title}, {configure, true},
 
398
              {width, W}, {height, H}],
 
399
    GS  = gs:start(),
 
400
    Win = gs:window(GS, WinOpt),
 
401
    Bar = gs:menubar(Win, []),
 
402
    create_file_menu(Bar),
 
403
    PackerOpt = [{packer_x, [{stretch, 1}]},
 
404
                 {packer_y, [{stretch, 1}, {fixed, 25}]},
 
405
                 {x, 0}, {y, 25}],
 
406
    Packer = gs:frame(Win, PackerOpt),
 
407
    EditorOpt = [{pack_xy, {1, 1}}, {vscroll, right}, {hscroll, bottom},
 
408
                 {wrap, none},
 
409
                 {bg, lightblue},  {font, {courier, 12}}],
 
410
    Editor = gs:editor(Packer, EditorOpt),
 
411
    FilteredEvent = config_editor(Editor, S),
 
412
    S2 = S#state{win = Win, packer = Packer, filtered_event = FilteredEvent},
 
413
    create_hide_menu(Bar, S2),
 
414
    create_search_menu(Bar, S2),
 
415
    create_filter_menu(Bar, S#state.filters),
 
416
    gs:config(Packer, [{width, W}, {height, H}]),
 
417
    gs:config(Win, [{map,true}, {keypress, true}]),
 
418
    S2.
 
419
 
 
420
create_file_menu(Bar) ->
 
421
    Button = gs:menubutton(Bar,  [{label, {text, "File"}}]),
 
422
    Menu  = gs:menu(Button, []),
 
423
    gs:menuitem(close, Menu,     [{label, {text,"Close (c)"}}]),
 
424
    gs:menuitem(save, Menu,      [{label, {text,"Save"}}]).
 
425
 
 
426
create_filter_menu(Bar, Filters) ->
 
427
    Button = gs:menubutton(Bar, [{label, {text, "Filters"}}]),
 
428
    Menu  = gs:menu(Button, []),
 
429
    gs:menuitem(Menu, [{label, {text, "Select Filter"}}, {bg, lightblue}, {enable, false}]),
 
430
    gs:menuitem(Menu, [{itemtype, separator}]),
 
431
    Item = fun(F, N) when F#filter.name =:= ?DEFAULT_FILTER_NAME->
 
432
                   Label = lists:concat([pad_string(F#filter.name, 20), "(0)"]),
 
433
                   gs:menuitem(Menu, [{label, {text, Label}}, {data, F}]),
 
434
                   N + 1;
 
435
              (F, N) ->
 
436
                   Name = F#filter.name,
 
437
                   Label = lists:concat([pad_string(Name, 20), "(", N, ")"]),
 
438
                   gs:menuitem(Menu, [{label, {text, Label}}, {data, F}]),
 
439
                   N + 1
 
440
           end,
 
441
    Filters2 = lists:keysort(#filter.name, Filters),
 
442
    lists:foldl(Item, 1, Filters2),
 
443
    Menu.
 
444
 
 
445
create_hide_menu(Bar, S) ->
 
446
    Button = gs:menubutton(Bar,  [{label, {text, "Hide"}}]),
 
447
    Menu   = gs:menu(Button, []),
 
448
    E      = S#state.filtered_event,
 
449
    From   = E#event.from,
 
450
    To     = E#event.to,
 
451
    if
 
452
        S#state.viewer_pid =:= undefined ->
 
453
            ignore;
 
454
        From =:= To ->
 
455
            gs:menuitem(Menu, [{label, {text, "Hide actor in Viewer "}}, {bg, lightblue}, {enable, false}]),
 
456
            gs:menuitem(Menu, [{itemtype, separator}]),
 
457
            gs:menuitem({hide, [From]},     Menu, [{label, {text,"From=To (f|t|b)"}}]),
 
458
            gs:menuitem(Menu, [{itemtype, separator}]),
 
459
            gs:menuitem(Menu, [{label, {text, "Show actor in Viewer "}}, {bg, lightblue}, {enable, false}]),
 
460
            gs:menuitem(Menu, [{itemtype, separator}]),
 
461
            gs:menuitem({show, [From]},     Menu, [{label, {text,"From=To (F|T|B)"}}]);
 
462
        true ->
 
463
            gs:menuitem(Menu, [{label, {text, "Hide actor in Viewer "}}, {bg, lightblue}, {enable, false}]),
 
464
            gs:menuitem(Menu, [{itemtype, separator}]),
 
465
            gs:menuitem({hide, [From]},     Menu, [{label, {text,"From (f)"}}]),
 
466
            gs:menuitem({hide, [To]},       Menu, [{label, {text,"To   (t)"}}]),
 
467
            gs:menuitem({hide, [From, To]}, Menu, [{label, {text,"Both (b)"}}]),
 
468
            gs:menuitem(Menu, [{itemtype, separator}]),
 
469
            gs:menuitem(Menu, [{label, {text, "Show actor in Viewer "}}, {bg, lightblue}, {enable, false}]),
 
470
            gs:menuitem(Menu, [{itemtype, separator}]),
 
471
            gs:menuitem({show, [From]},     Menu, [{label, {text,"From (F)"}}]),
 
472
            gs:menuitem({show, [To]},       Menu, [{label, {text,"To   (T)"}}]),
 
473
            gs:menuitem({show, [From, To]}, Menu, [{label, {text,"Both (B)"}}])
 
474
    end.
 
475
 
 
476
create_search_menu(Bar, S) ->
 
477
    Button = gs:menubutton(Bar,  [{label, {text, "Search"}}]),
 
478
    Menu   = gs:menu(Button, []),
 
479
    E      = S#state.filtered_event,
 
480
    From   = E#event.from,
 
481
    To     = E#event.to,
 
482
    gs:menuitem(Menu, [{label, {text, "Search in Viewer "}},
 
483
                       {bg, lightblue}, {enable, false}]),
 
484
    gs:menuitem(Menu, [{itemtype, separator}]),
 
485
    if
 
486
        S#state.viewer_pid =:= undefined ->
 
487
            S;
 
488
        From =:= To  ->
 
489
            Key = et_collector:make_key(S#state.event_order, E),
 
490
            ModeS = {search_actors, forward, Key, [From]},
 
491
            ModeR = {search_actors, reverse, Key, [From]},
 
492
            gs:menuitem({mode, ModeS}, Menu, [{label, {text,"Forward from this event   (s)"}}]),
 
493
            gs:menuitem({mode, ModeR}, Menu, [{label, {text,"Reverse from this event   (r)"}}]);
 
494
        true ->
 
495
            Key = et_collector:make_key(S#state.event_order, E),
 
496
            ModeS = {search_actors, forward, Key, [From, To]},
 
497
            ModeR = {search_actors, reverse, Key, [From, To]},
 
498
            gs:menuitem({mode, ModeS}, Menu, [{label, {text,"Forward from this event   (s)"}}]),
 
499
            gs:menuitem({mode, ModeR}, Menu, [{label, {text,"Reverse from this event   (r)"}}])
 
500
    end,
 
501
    gs:menuitem({mode, all}, Menu,   [{label, {text,"Abort search. Display all (a)"}}]).
 
502
 
 
503
config_editor(Editor, S) ->
 
504
    Event = S#state.event,
 
505
    Name = S#state.active_filter,
 
506
    {value, F} = lists:keysearch(Name, #filter.name, S#state.filters),
 
507
    FilterFun = F#filter.function,
 
508
    case catch FilterFun(Event) of
 
509
        true ->
 
510
            do_config_editor(Editor, Event, lightblue, S#state.event_order);
 
511
        {true, Event2} when is_record(Event2, event) ->
 
512
            do_config_editor(Editor, Event2, lightblue, S#state.event_order);
 
513
        false ->
 
514
            do_config_editor(Editor, Event, red, S#state.event_order);
 
515
        Bad ->
 
516
            Contents = {bad_filter, Name, Bad},
 
517
            BadEvent = Event#event{contents = Contents},
 
518
            do_config_editor(Editor, BadEvent, red, S#state.event_order)
 
519
    end.
 
520
 
 
521
do_config_editor(Editor, Event, Colour, TsKey) ->
 
522
    String = event_to_string(Event, TsKey),
 
523
    gs:config(Editor, {insert, {'end', String}}),
 
524
    gs:config(Editor, {enable, false}),
 
525
    gs:config(Editor, {bg, Colour}),
 
526
    Event.
 
527
 
 
528
%%%----------------------------------------------------------------------
 
529
%%% String handling
 
530
%%%----------------------------------------------------------------------
 
531
 
 
532
term_to_string(Term) ->
 
533
    case catch io_lib:format("~s", [Term]) of
 
534
        {'EXIT', _} -> io_lib:format("~p", [Term]);
 
535
        GoodString  -> GoodString
 
536
    end.
 
537
 
 
538
now_to_string({Mega, Sec, Micro} = Now)
 
539
  when is_integer(Mega), is_integer(Sec), is_integer(Micro) ->
 
540
    {{Y, Mo, D}, {H, Mi, S}} = calendar:now_to_universal_time(Now),
 
541
    lists:concat([Y, "-", Mo, "-", D, " ", H, ".", Mi, ".", S, ".", Micro]);
 
542
now_to_string(Other) ->
 
543
    term_to_string(Other).
 
544
 
 
545
event_to_string(Event, TsKey) ->
 
546
    ReportedTs = Event#event.trace_ts,
 
547
    ParsedTs   = Event#event.event_ts,
 
548
    Deep = 
 
549
        ["DETAIL LEVEL: ", term_to_string(Event#event.detail_level),
 
550
         "\nLABEL:        ", term_to_string(Event#event.label),
 
551
         case Event#event.from =:= Event#event.to of
 
552
             true ->
 
553
                 ["\nACTOR:        ", term_to_string(Event#event.from)];
 
554
             false ->
 
555
                 ["\nFROM:         ", term_to_string(Event#event.from),
 
556
                  "\nTO:           ", term_to_string(Event#event.to)]
 
557
         end,
 
558
         case ReportedTs =:= ParsedTs of
 
559
             true ->
 
560
                 ["\nPARSED:       ", now_to_string(ParsedTs)];
 
561
             false ->
 
562
                 case TsKey of
 
563
                     trace_ts ->
 
564
                         ["\nTRACE_TS:     ", now_to_string(ReportedTs),
 
565
                          "\nEVENT_TS:     ", now_to_string(ParsedTs)];
 
566
                     event_ts ->
 
567
                         ["\nEVENT_TS:     ", now_to_string(ParsedTs),
 
568
                          "\nTRACE_TS:     ", now_to_string(ReportedTs)]
 
569
                 end
 
570
         end,
 
571
         "\nCONTENTS:\n\n", term_to_string(Event#event.contents)],
 
572
    lists:flatten(Deep).
 
573
 
 
574
pad_string(Atom, MinLen) when is_atom(Atom) ->
 
575
    pad_string(atom_to_list(Atom), MinLen);
 
576
pad_string(String, MinLen) when is_integer(MinLen), MinLen >= 0 ->
 
577
    Len = length(String),
 
578
    case Len >= MinLen of
 
579
        true ->
 
580
            String;
 
581
        false ->
 
582
            String ++ lists:duplicate(MinLen - Len, $ )
 
583
    end.
 
584
 
 
585
send_viewer_event(S, Event)  ->
 
586
    case S#state.viewer_pid of
 
587
        ViewerPid when is_pid(ViewerPid) ->
 
588
            ViewerPid ! {et, Event};
 
589
        undefined  ->
 
590
            ignore
 
591
    end.