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

« back to all changes in this revision

Viewing changes to lib/et/src/et_wx_contents_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 2000-2009. 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_wx_contents_viewer).
 
24
 
 
25
-behaviour(wx_object).
 
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
         handle_event/2]).
 
35
 
 
36
-include("../include/et.hrl").
 
37
-include("et_internal.hrl").
 
38
-include_lib("wx/include/wx.hrl").
 
39
 
 
40
-record(state, {parent_pid,     % Pid of parent process
 
41
                viewer_pid,     % Pid of viewer process
 
42
                event_order,    % Field to be used as primary key
 
43
                event,          % The original event
 
44
                filtered_event, % Event processed by active filter
 
45
                active_filter,  % Name of the active filter
 
46
                filters,        % List of possible filters
 
47
                win,            % GUI: Frame object
 
48
                frame,          % GUI: Frame object
 
49
                panel,          % GUI: Panel object
 
50
                width,          % GUI: Window width
 
51
                height,
 
52
                editor,
 
53
                menu_data,      % GUI: Window height
 
54
                wx_debug,       % GUI: WX debug level
 
55
                trap_exit}).    % trap_exit process flag
 
56
 
 
57
%%%----------------------------------------------------------------------
 
58
%%% Client side
 
59
%%%----------------------------------------------------------------------
 
60
 
 
61
%%----------------------------------------------------------------------
 
62
%% start_link(Options) -> {ok, ContentsPid} | {error, Reason}
 
63
%%
 
64
%% Start a viewer for the event contents as window in GS
 
65
%%
 
66
%% Options = [option()]
 
67
%% 
 
68
%% option() =
 
69
%% 
 
70
%%   {parent_pid, pid()}          |  % Pid of parent process
 
71
%%   {viewer_pid, pid()}          |  % Pid of viewer process
 
72
%%   {event_order, event_order()} |  % Field to be used as primary key 
 
73
%%   {active_filter, atom()}      |  % Name of the active filter
 
74
%%   {filter, atom(), fun()}         % A named filter fun
 
75
%%   
 
76
%% event_order() = 'trace_ts' | 'event_ts'
 
77
%% ContentsPid = pid()
 
78
%% Reason = term()
 
79
%%----------------------------------------------------------------------
 
80
 
 
81
start_link(Options) ->
 
82
    case parse_opt(Options, default_state()) of
 
83
        {ok, S} ->
 
84
            try
 
85
                WxRef = wx_object:start_link(?MODULE, [S], []),
 
86
                Pid = wx_object:get_pid(WxRef),
 
87
                if
 
88
                    S#state.parent_pid =/= self() ->
 
89
                        unlink(Pid);
 
90
                    true ->
 
91
                        ignore
 
92
                end,
 
93
                {ok, Pid}
 
94
            catch
 
95
                error:Reason ->
 
96
                    {error, {'EXIT', Reason, erlang:get_stacktrace()}}
 
97
            end;
 
98
        {error, Reason} ->
 
99
            {error, Reason}
 
100
    end.
 
101
 
 
102
default_state() ->
 
103
    #state{parent_pid    = self(),
 
104
           viewer_pid    = undefined,
 
105
           active_filter = ?DEFAULT_FILTER_NAME,
 
106
           filters       = [?DEFAULT_FILTER],
 
107
           width         = 600,
 
108
           height        = 300,
 
109
           wx_debug      = 0,
 
110
           trap_exit     = true}.
 
111
 
 
112
parse_opt([], S) ->
 
113
    Name = S#state.active_filter,
 
114
    Filters = S#state.filters,
 
115
    if
 
116
        S#state.event =:= undefined ->
 
117
            {error, {badarg, no_event}};
 
118
        is_atom(Name) ->
 
119
            case lists:keysearch(Name, #filter.name, Filters) of
 
120
                {value, F} when is_record(F, filter) ->
 
121
                    {ok, S#state{active_filter = Name}};
 
122
                false ->
 
123
                    {error, {badarg, {no_such_filter, Name, Filters}}}
 
124
            end
 
125
    end;
 
126
parse_opt([H | T], S) ->
 
127
    case H of
 
128
        {parent_pid, ParentPid} when is_pid(ParentPid); ParentPid =:= undefined ->
 
129
            parse_opt(T, S#state{parent_pid = ParentPid});
 
130
        {viewer_pid, ViewerPid} when is_pid(ViewerPid) ->
 
131
            parse_opt(T, S#state{viewer_pid = ViewerPid});
 
132
        {wx_debug, Level} ->
 
133
            parse_opt(T, S#state{wx_debug = Level});
 
134
        {trap_exit, Bool} when Bool =:= true; Bool =:= false->
 
135
            parse_opt(T, S#state{trap_exit = Bool});
 
136
        {event_order, trace_ts} ->
 
137
            parse_opt(T, S#state{event_order = trace_ts});
 
138
        {event_order, event_ts} ->
 
139
            parse_opt(T, S#state{event_order = event_ts});
 
140
        {event, Event} when is_record(Event, event) ->
 
141
            parse_opt(T, S#state{event = Event});
 
142
        {active_filter, Name} when is_atom(Name) ->
 
143
            parse_opt(T, S#state{active_filter = Name});
 
144
        F when is_record(F, filter),
 
145
               is_atom(F#filter.name),
 
146
               is_function(F#filter.function) ->
 
147
            Filters = lists:keydelete(F#filter.name, #filter.name, S#state.filters),
 
148
            Filters2 = lists:keysort(#filter.name, [F | Filters]),
 
149
            parse_opt(T, S#state{filters = Filters2});
 
150
        {width, Width} when is_integer(Width), Width > 0 ->
 
151
            parse_opt(T, S#state{width = Width});
 
152
        {height, Height} when is_integer(Height), Height > 0 ->
 
153
            parse_opt(T, S#state{height = Height});
 
154
        Bad ->
 
155
            {error, {bad_option, Bad}}
 
156
    end;
 
157
parse_opt(BadList, _S) ->
 
158
    {error, {bad_option_list, BadList}}.
 
159
 
 
160
%%----------------------------------------------------------------------
 
161
%% stop(ContentsPid) -> ok
 
162
%%
 
163
%% Stops a contents viewer process
 
164
%%
 
165
%% ContentsPid = pid()
 
166
%%----------------------------------------------------------------------
 
167
 
 
168
stop(ContentsPid) when is_pid(ContentsPid) ->
 
169
    Type = process,
 
170
    MonitorRef = erlang:monitor(Type, ContentsPid),
 
171
    ContentsPid ! {stop, self()},
 
172
    receive
 
173
        {'DOWN', MonitorRef, Type, ContentsPid, shutdown} ->
 
174
            ok;
 
175
        {'DOWN', MonitorRef, Type, ContentsPid, Reason} ->
 
176
            {error, Reason}
 
177
    end.
 
178
 
 
179
%% call(Frame, Request) ->
 
180
%%     wx_object:call(Frame, Request, infinity).
 
181
 
 
182
%%%----------------------------------------------------------------------
 
183
%%% Callback functions from gen_server
 
184
%%%----------------------------------------------------------------------
 
185
 
 
186
%%----------------------------------------------------------------------
 
187
%% Func: init/1
 
188
%% Returns: {ok, State}          |
 
189
%%          {ok, State, Timeout} |
 
190
%%          ignore               |
 
191
%%          {stop, Reason}
 
192
%%----------------------------------------------------------------------
 
193
 
 
194
init([S]) when is_record(S, state) ->
 
195
    process_flag(trap_exit, S#state.trap_exit),
 
196
    case S#state.parent_pid of
 
197
        undefined -> ok;
 
198
        ParentPid -> link(ParentPid)
 
199
    end,
 
200
    wx:debug(S#state.wx_debug),
 
201
    S2 = create_window(S),
 
202
    {S2#state.frame, S2}.
 
203
 
 
204
%%----------------------------------------------------------------------
 
205
%% Func: handle_call/3
 
206
%% Returns: {reply, Reply, State}          |
 
207
%%          {reply, Reply, State, Timeout} |
 
208
%%          {noreply, State}               |
 
209
%%          {noreply, State, Timeout}      |
 
210
%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
 
211
%%          {stop, Reason, State}            (terminate/2 is called)
 
212
%%----------------------------------------------------------------------
 
213
 
 
214
handle_call(Request, From, S) ->
 
215
    ok = error_logger:format("~p(~p): handle_call(~p, ~p, ~p)~n",
 
216
                             [?MODULE, self(), Request, From, S]),
 
217
    Reply = {error, {bad_request, Request}},
 
218
    {reply, Reply, S}.
 
219
 
 
220
%%----------------------------------------------------------------------
 
221
%% Func: handle_cast/2
 
222
%% Returns: {noreply, State}          |
 
223
%%          {noreply, State, Timeout} |
 
224
%%          {stop, Reason, State}            (terminate/2 is called)
 
225
%%----------------------------------------------------------------------
 
226
 
 
227
handle_cast(Msg, S) ->
 
228
    ok = error_logger:format("~p(~p): handle_cast(~p, ~p)~n",
 
229
                             [?MODULE, self(), Msg, S]),
 
230
    {noreply, S}.
 
231
 
 
232
%%----------------------------------------------------------------------
 
233
%% Func: handle_event/2
 
234
%% Returns: {noreply, State}          |
 
235
%%          {noreply, State, Timeout} |
 
236
%%          {stop, Reason, State}            (terminate/2 is called)
 
237
%%----------------------------------------------------------------------
 
238
 
 
239
handle_event(#wx{id = Id,
 
240
                 event = #wxCommand{type = command_menu_selected}}, 
 
241
             S) ->
 
242
    case proplists:get_value(Id, S#state.menu_data) of
 
243
        undefined ->
 
244
            ignore;
 
245
        Data when is_record(Data, filter) ->
 
246
            F = Data,
 
247
            ChildState= S#state{active_filter = F#filter.name},
 
248
            case wx_object:start_link(?MODULE, [ChildState], []) of
 
249
                {ok, Pid} when S#state.parent_pid =/= self() ->
 
250
                    unlink(Pid);
 
251
                _ ->
 
252
                    ignore
 
253
            end;
 
254
        {hide, Actors} ->
 
255
            send_viewer_event(S, {delete_actors, Actors});
 
256
        {show, Actors} ->
 
257
            send_viewer_event(S, {insert_actors, Actors});
 
258
        {mode, Mode} ->
 
259
            send_viewer_event(S, {mode, Mode});
 
260
        Nyi ->
 
261
            ok = error_logger:format("~p: click ~p ignored (nyi)~n",
 
262
                                     [?MODULE, Nyi])
 
263
    end,
 
264
    case Id of
 
265
        ?wxID_EXIT ->
 
266
            wxFrame:destroy(S#state.frame),
 
267
            opt_unlink(S#state.parent_pid),
 
268
            {stop, shutdown, S};
 
269
        ?wxID_SAVE ->
 
270
            Event = S#state.event,
 
271
            TimeStamp = 
 
272
                case S#state.event_order of
 
273
                    trace_ts -> Event#event.trace_ts;
 
274
                    event_ts   -> Event#event.event_ts
 
275
                end,
 
276
            FileName = lists:flatten(["et_contents_viewer_", now_to_string(TimeStamp), ".txt"]),
 
277
            Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT,
 
278
            Msg = "Select a file to the events to",
 
279
            case select_file(S#state.frame, Msg, filename:absname(FileName), Style) of
 
280
                {ok, FileName2} ->
 
281
                    Bin = list_to_binary(event_to_string(Event, S#state.event_order)),
 
282
                    file:write_file(FileName2, Bin);
 
283
                cancel ->
 
284
                    ok
 
285
            end,
 
286
            {noreply, S};
 
287
        ?wxID_PRINT ->
 
288
            Html = wxHtmlEasyPrinting:new([{parentWindow, S#state.win}]),
 
289
            Text =  "<pre>" ++ wxTextCtrl:getValue(S#state.editor) ++ "</pre>",
 
290
            wxHtmlEasyPrinting:previewText(Html, Text),
 
291
            {noreply, S};
 
292
        _ ->
 
293
            {noreply, S}
 
294
    end;
 
295
handle_event(#wx{event = #wxKey{rawCode = KeyCode}}, S) ->
 
296
    case KeyCode of
 
297
        $c ->
 
298
            wxFrame:destroy(S#state.frame),
 
299
            opt_unlink(S#state.parent_pid),
 
300
            {stop, normal, S};
 
301
        $f ->
 
302
            E    = S#state.filtered_event,
 
303
            From = E#event.from,
 
304
            send_viewer_event(S, {delete_actors, [From]}),
 
305
            {noreply, S};
 
306
        $t ->
 
307
            E  = S#state.filtered_event,
 
308
            To = E#event.to,
 
309
            send_viewer_event(S, {delete_actors, [To]}),
 
310
            {noreply, S};
 
311
        $b ->
 
312
            E    = S#state.filtered_event,
 
313
            From = E#event.from,
 
314
            To   = E#event.to,
 
315
            send_viewer_event(S, {delete_actors, [From, To]}),
 
316
            {noreply, S};
 
317
        
 
318
        $F ->
 
319
            E    = S#state.filtered_event,
 
320
            From = E#event.from,
 
321
            send_viewer_event(S, {insert_actors, [From]}),
 
322
            {noreply, S};
 
323
        $T ->
 
324
            E  = S#state.filtered_event,
 
325
            To = E#event.to,
 
326
            send_viewer_event(S, {insert_actors, [To]}),
 
327
            {noreply, S};
 
328
        $B ->
 
329
            E    = S#state.filtered_event,
 
330
            From = E#event.from,
 
331
            To   = E#event.to,
 
332
            send_viewer_event(S, {insert_actors, [From, To]}),
 
333
            {noreply, S};
 
334
 
 
335
        $s ->
 
336
            E     = S#state.filtered_event,
 
337
            From  = E#event.from,
 
338
            To    = E#event.to,
 
339
            First = et_collector:make_key(S#state.event_order, E),
 
340
            Mode  = {search_actors, forward, First, [From, To]},
 
341
            send_viewer_event(S, {mode, Mode}),
 
342
            {noreply, S};
 
343
        $r ->
 
344
            E     = S#state.filtered_event,
 
345
            From  = E#event.from,
 
346
            To    = E#event.to,
 
347
            First = et_collector:make_key(S#state.event_order, E),
 
348
            Mode  = {search_actors, reverse, First, [From, To]},
 
349
            send_viewer_event(S, {mode, Mode}),
 
350
            {noreply, S};
 
351
        $a ->
 
352
            send_viewer_event(S, {mode, all}),
 
353
            {noreply, S};
 
354
 
 
355
        $0 ->
 
356
            case lists:keysearch(?DEFAULT_FILTER_NAME, #filter.name, S#state.filters) of
 
357
                {value, F} when is_record(F, filter) ->
 
358
                    ChildState= S#state{active_filter = F#filter.name},
 
359
                    case wx_object:start_link(?MODULE, [ChildState], []) of
 
360
                        {ok, Pid} when S#state.parent_pid =/= self() ->
 
361
                            unlink(Pid);
 
362
                        _ ->
 
363
                            ignore
 
364
                    end;
 
365
                false ->
 
366
                    ignore
 
367
            end,
 
368
            {noreply, S};
 
369
        Int when is_integer(Int), Int > $0, Int =< $9 ->
 
370
            case catch lists:nth(Int-$0, S#state.filters) of
 
371
                F when is_record(F, filter) ->
 
372
                    ChildState= S#state{active_filter = F#filter.name},
 
373
                    case wx_object:start_link(?MODULE, [ChildState], []) of
 
374
                        {ok, Pid} when S#state.parent_pid =/= self() ->
 
375
                            unlink(Pid);
 
376
                        _ ->
 
377
                            ignore
 
378
                    end;
 
379
                {'EXIT', _} ->
 
380
                    ignore
 
381
            end,
 
382
            {noreply, S};
 
383
 
 
384
        _ ->
 
385
            io:format("~p: ignored: ~p~n", [?MODULE, KeyCode]),
 
386
            {noreply, S}
 
387
    end;
 
388
handle_event(#wx{event = #wxClose{}}, S) ->
 
389
    opt_unlink(S#state.parent_pid),
 
390
    {stop, shutdown, S};
 
391
handle_event(#wx{event = #wxSize{size = {W, H}}}, S) ->
 
392
    S2 = S#state{width = W, height = H},
 
393
    {noreply, S2};
 
394
handle_event(Wx = #wx{}, S) ->
 
395
    io:format("~p got an unexpected event: ~p\n", [self(), Wx]),
 
396
    {noreply, S}.
 
397
 
 
398
%%----------------------------------------------------------------------
 
399
%% Func: handle_info/2
 
400
%% Returns: {noreply, State}          |
 
401
%%          {noreply, State, Timeout} |
 
402
%%          {stop, Reason, State}            (terminate/2 is called)
 
403
%%----------------------------------------------------------------------
 
404
 
 
405
handle_info({stop, _From}, S) ->
 
406
    wxFrame:destroy(S#state.frame),
 
407
    opt_unlink(S#state.parent_pid),
 
408
    {stop, shutdown, S};
 
409
handle_info({'EXIT', Pid, Reason}, S) ->
 
410
    if
 
411
        Pid =:= S#state.parent_pid ->
 
412
            wxFrame:destroy(S#state.frame),
 
413
            opt_unlink(S#state.parent_pid),
 
414
            {stop, Reason, S};
 
415
        true ->
 
416
            {noreply, S}
 
417
    end;
 
418
handle_info(Info, S) ->
 
419
    ok = error_logger:format("~p(~p): handle_info(~p, ~p)~n",
 
420
                             [?MODULE, self(), Info, S]),
 
421
    {noreply, S}.
 
422
 
 
423
%%----------------------------------------------------------------------
 
424
%% Func: terminate/2
 
425
%% Purpose: Shutdown the server
 
426
%% Returns: any (ignored by gen_server)
 
427
%%----------------------------------------------------------------------
 
428
 
 
429
terminate(_Reason, _S) ->
 
430
    ignore.
 
431
 
 
432
%%----------------------------------------------------------------------
 
433
%% Func: code_change/3
 
434
%% Purpose: Convert process state when code is changed
 
435
%% Returns: {ok, NewState}
 
436
%%----------------------------------------------------------------------
 
437
 
 
438
code_change(_OldVsn, S, _Extra) ->
 
439
    {ok, S}.
 
440
 
 
441
%%%----------------------------------------------------------------------
 
442
%%% Handle graphics
 
443
%%%----------------------------------------------------------------------
 
444
 
 
445
opt_unlink(Pid) ->
 
446
    if
 
447
        Pid =:= undefined ->
 
448
            ignore;
 
449
        true ->
 
450
            unlink(Pid)
 
451
    end.
 
452
 
 
453
create_window(S) ->
 
454
    H = S#state.height,
 
455
    W = S#state.width,
 
456
    Name = S#state.active_filter,
 
457
    Title = lists:concat([?MODULE, " (filter: ", Name, ")"]),
 
458
    WinOpt = [{size, {W,H}}],
 
459
    Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title, WinOpt),
 
460
    wxFrame:createStatusBar(Frame),
 
461
 
 
462
    Panel = wxPanel:new(Frame, []),
 
463
    Bar = wxMenuBar:new(),
 
464
    wxFrame:setMenuBar(Frame,Bar),
 
465
    create_file_menu(Bar),
 
466
    Editor = wxTextCtrl:new(Panel, ?wxID_ANY, [{style, 0
 
467
                                                bor  ?wxDEFAULT
 
468
                                                bor ?wxTE_MULTILINE
 
469
                                                bor ?wxTE_READONLY
 
470
                                                bor ?wxTE_DONTWRAP}]),
 
471
    Font = wxFont:new(10, ?wxFONTFAMILY_TELETYPE, ?wxNORMAL, ?wxNORMAL,[]),
 
472
    TextAttr = wxTextAttr:new(?wxBLACK, [{font, Font}]),
 
473
    wxTextCtrl:setDefaultStyle(Editor, TextAttr),
 
474
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
475
    wxSizer:add(Sizer, Editor, [{flag, ?wxEXPAND}, {proportion, 1}]),
 
476
    FilteredEvent = config_editor(Editor, S),
 
477
    S2 = S#state{win = Frame, panel = Panel, filtered_event = FilteredEvent},
 
478
    HideData = create_hide_menu(Bar, S2),
 
479
    SearchData = create_search_menu(Bar, S2),
 
480
    FilterData = create_filter_menu(Bar, S#state.filters),
 
481
    wxFrame:connect(Frame, command_menu_selected, []),
 
482
    wxFrame:connect(Frame, key_up),
 
483
    wxFrame:connect(Frame, close_window, [{skip,true}]),
 
484
    wxFrame:setFocus(Frame),
 
485
    wxPanel:setSizer(Panel, Sizer),
 
486
    wxFrame:show(Frame),
 
487
    S2#state{menu_data = HideData++SearchData++FilterData, editor = Editor, frame = Frame}.
 
488
 
 
489
menuitem(Menu, Id, Text, UserData) ->
 
490
    Item = wxMenu:append(Menu, Id, Text),
 
491
    {wxMenuItem:getId(Item), UserData}.
 
492
 
 
493
create_file_menu(Bar) ->
 
494
    Menu = wxMenu:new([]),
 
495
    wxMenu:append(Menu, ?wxID_SAVE, "Save"),
 
496
    wxMenu:append(Menu, ?wxID_PRINT,"Print"),
 
497
    wxMenu:appendSeparator(Menu),
 
498
    wxMenu:append(Menu, ?wxID_EXIT, "Close"),
 
499
    wxMenuBar:append(Bar, Menu, "File").
 
500
 
 
501
create_filter_menu(Bar, Filters) ->
 
502
    Menu  = wxMenu:new([]),
 
503
    wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Select Filter"), [{enable, false}]),
 
504
    wxMenu:appendSeparator(Menu),
 
505
    Item = fun(F, {N,Acc}) when F#filter.name =:= ?DEFAULT_FILTER_NAME->
 
506
                   Label = lists:concat([pad_string(F#filter.name, 20, $\ , right), "(0)"]),
 
507
                   MenuItem = menuitem(Menu, ?wxID_ANY, Label, F),
 
508
                   {N + 1, [MenuItem|Acc]};
 
509
              (F, {N, Acc}) ->
 
510
                   Name = F#filter.name,
 
511
                   Label = lists:concat([pad_string(Name, 20, $\ , right), "(", N, ")"]),
 
512
                   MenuItem = menuitem(Menu, ?wxID_ANY, Label, F),
 
513
                   {N + 1, [MenuItem|Acc]}
 
514
           end,
 
515
    Filters2 = lists:keysort(#filter.name, Filters),
 
516
    {_,MenuData} = lists:foldl(Item, {1, []}, Filters2),
 
517
    wxMenuBar:append(Bar, Menu, "Filters"),
 
518
    MenuData.
 
519
 
 
520
create_hide_menu(Bar, S) ->
 
521
    Menu   = wxMenu:new([]),
 
522
    E      = S#state.filtered_event,
 
523
    From   = E#event.from,
 
524
    To     = E#event.to,
 
525
    MenuData =
 
526
        if
 
527
            S#state.viewer_pid =:= undefined ->
 
528
                ignore;
 
529
            From =:= To ->
 
530
                wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Hide actor in Viewer "),
 
531
                                  [{enable, false}]),
 
532
                wxMenu:appendSeparator(Menu),
 
533
                Hide = menuitem(Menu, ?wxID_ANY, "From=To (f|t|b)", {hide, [From]}),
 
534
                wxMenu:appendSeparator(Menu),
 
535
                wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Show actor in Viewer "),
 
536
                                  [{enable, false}]),
 
537
                wxMenu:appendSeparator(Menu),
 
538
                Show = menuitem(Menu, ?wxID_ANY, "From=To (F|T|B)", {show, [From]}),
 
539
                [Show,Hide];
 
540
            true ->
 
541
                wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Hide actor in Viewer "),
 
542
                                   [{enable, false}]),
 
543
                 wxMenu:appendSeparator(Menu),
 
544
                Hide = [menuitem(Menu, ?wxID_ANY, "From (f)", {hide, [From]}),
 
545
                        menuitem(Menu, ?wxID_ANY, "To   (t)", {hide, [To]}),
 
546
                        menuitem(Menu, ?wxID_ANY, "Both (b)", {hide, [From, To]})],
 
547
                wxMenu:appendSeparator(Menu),
 
548
                wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Show actor in Viewer "),
 
549
                                  [{enable, false}]),
 
550
                wxMenu:appendSeparator(Menu),
 
551
                Show = [menuitem(Menu, ?wxID_ANY, "From (F)", {show, [From]}),
 
552
                        menuitem(Menu, ?wxID_ANY, "To   (T)", {show, [To]}),
 
553
                        menuitem(Menu, ?wxID_ANY, "Both (B)", {show, [From, To]})],
 
554
                Show++Hide
 
555
        end,
 
556
    wxMenuBar:append(Bar, Menu, "Hide"),
 
557
    MenuData.
 
558
 
 
559
create_search_menu(Bar, S) ->
 
560
    Menu   = wxMenu:new([]),
 
561
    E      = S#state.filtered_event,
 
562
    From   = E#event.from,
 
563
    To     = E#event.to,
 
564
    wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Search in Viewer "),
 
565
                      [{enable, false}]),
 
566
    wxMenu:appendSeparator(Menu),
 
567
    MenuData =
 
568
        if
 
569
            S#state.viewer_pid =:= undefined ->
 
570
                [menuitem(Menu, ?wxID_ANY, "Abort search. Display all (a)", {mode, all})];
 
571
            From =:= To  ->
 
572
                Key = et_collector:make_key(S#state.event_order, E),
 
573
                ModeS = {search_actors, forward, Key, [From]},
 
574
                ModeR = {search_actors, reverse, Key, [From]},
 
575
                [menuitem(Menu, ?wxID_ANY, "Forward from this event   (s)", {mode, ModeS}),
 
576
                 menuitem(Menu, ?wxID_ANY, "Reverse from this event   (r)", {mode, ModeR}),
 
577
                 menuitem(Menu, ?wxID_ANY, "Abort search. Display all (a)", {mode, all})];
 
578
            true ->
 
579
                Key = et_collector:make_key(S#state.event_order, E),
 
580
                ModeS = {search_actors, forward, Key, [From, To]},
 
581
                ModeR = {search_actors, reverse, Key, [From, To]},
 
582
                [menuitem(Menu, ?wxID_ANY, "Forward from this event   (s)", {mode, ModeS}),
 
583
                 menuitem(Menu, ?wxID_ANY, "Reverse from this event   (r)", {mode, ModeR}),
 
584
                 menuitem(Menu, ?wxID_ANY, "Abort search. Display all (a)", {mode, all})]
 
585
        end,
 
586
    wxMenuBar:append(Bar, Menu, "Search"),
 
587
    MenuData.
 
588
 
 
589
config_editor(Editor, S) ->
 
590
    Event = S#state.event,
 
591
    Name = S#state.active_filter,
 
592
    {value, F} = lists:keysearch(Name, #filter.name, S#state.filters),
 
593
    FilterFun = F#filter.function,
 
594
    case catch FilterFun(Event) of
 
595
        true ->
 
596
            do_config_editor(Editor, Event, lightblue, S#state.event_order);
 
597
        {true, Event2} when is_record(Event2, event) ->
 
598
            do_config_editor(Editor, Event2, lightblue, S#state.event_order);
 
599
        false ->
 
600
            do_config_editor(Editor, Event, red, S#state.event_order);
 
601
        Bad ->
 
602
            Contents = {bad_filter, Name, Bad},
 
603
            BadEvent = Event#event{contents = Contents},
 
604
            do_config_editor(Editor, BadEvent, red, S#state.event_order)
 
605
    end.
 
606
 
 
607
do_config_editor(Editor, Event, _Colour, TsKey) ->
 
608
    String = event_to_string(Event, TsKey),
 
609
    wxTextCtrl:appendText(Editor, String),
 
610
    Event.
 
611
 
 
612
%%%----------------------------------------------------------------------
 
613
%%% String handling
 
614
%%%----------------------------------------------------------------------
 
615
 
 
616
term_to_string(Term) ->
 
617
    case catch io_lib:format("~s", [Term]) of
 
618
        {'EXIT', _} -> io_lib:format("~p", [Term]);
 
619
        GoodString  -> GoodString
 
620
    end.
 
621
 
 
622
now_to_string({Mega, Sec, Micro} = Now)
 
623
  when is_integer(Mega), is_integer(Sec), is_integer(Micro) ->
 
624
    {{Y, Mo, D}, {H, Mi, S}} = calendar:now_to_universal_time(Now),
 
625
    lists:concat([Y, "-", 
 
626
                  pad_string(Mo, 2, $0, left), "-", 
 
627
                  pad_string(D, 2, $0, left),
 
628
                  "T",
 
629
                  pad_string(H, 2, $0, left), ":",
 
630
                  pad_string(Mi, 2, $0, left), ":",
 
631
                  pad_string(S, 2, $0, left), ".", 
 
632
                  Micro]);
 
633
now_to_string(Other) ->
 
634
    term_to_string(Other).
 
635
 
 
636
event_to_string(Event, TsKey) ->
 
637
    ReportedTs = Event#event.trace_ts,
 
638
    ParsedTs   = Event#event.event_ts,
 
639
    Deep = 
 
640
        ["DETAIL LEVEL: ", term_to_string(Event#event.detail_level),
 
641
         "\nLABEL:        ", term_to_string(Event#event.label),
 
642
         case Event#event.from =:= Event#event.to of
 
643
             true ->
 
644
                 ["\nACTOR:        ", term_to_string(Event#event.from)];
 
645
             false ->
 
646
                 ["\nFROM:         ", term_to_string(Event#event.from),
 
647
                  "\nTO:           ", term_to_string(Event#event.to)]
 
648
         end,
 
649
         case ReportedTs =:= ParsedTs of
 
650
             true ->
 
651
                 ["\nPARSED:       ", now_to_string(ParsedTs)];
 
652
             false ->
 
653
                 case TsKey of
 
654
                     trace_ts ->
 
655
                         ["\nTRACE_TS:     ", now_to_string(ReportedTs),
 
656
                          "\nEVENT_TS:     ", now_to_string(ParsedTs)];
 
657
                     event_ts ->
 
658
                         ["\nEVENT_TS:     ", now_to_string(ParsedTs),
 
659
                          "\nTRACE_TS:     ", now_to_string(ReportedTs)]
 
660
                 end
 
661
         end,
 
662
         "\nCONTENTS:\n\n", term_to_string(Event#event.contents)],
 
663
    lists:flatten(Deep).
 
664
 
 
665
pad_string(Int, MinLen, Char, Dir) when is_integer(Int) ->
 
666
    pad_string(integer_to_list(Int), MinLen, Char, Dir);
 
667
pad_string(Atom, MinLen, Char, Dir) when is_atom(Atom) ->
 
668
    pad_string(atom_to_list(Atom), MinLen, Char, Dir);
 
669
pad_string(String, MinLen, Char, Dir) when is_integer(MinLen), MinLen >= 0 ->
 
670
    Len = length(String),
 
671
    case {Len >= MinLen, Dir} of
 
672
        {true, _} ->
 
673
            String;
 
674
        {false, right} ->
 
675
            String ++ lists:duplicate(MinLen - Len, Char);
 
676
        {false, left} ->
 
677
            lists:duplicate(MinLen - Len, Char) ++ String
 
678
    end.
 
679
 
 
680
send_viewer_event(S, Event)  ->
 
681
    case S#state.viewer_pid of
 
682
        ViewerPid when is_pid(ViewerPid) ->
 
683
            ViewerPid ! {et, Event};
 
684
        undefined  ->
 
685
            ignore
 
686
    end.
 
687
 
 
688
select_file(Frame, Message, DefaultFile, Style) ->
 
689
    Dialog = wxFileDialog:new(Frame,
 
690
                              [{message, Message},
 
691
                               {defaultDir, filename:dirname(DefaultFile)},
 
692
                               {defaultFile, filename:basename(DefaultFile)},
 
693
                               {style, Style}]),
 
694
    Choice = 
 
695
        case wxMessageDialog:showModal(Dialog) of
 
696
            ?wxID_CANCEL ->  cancel;
 
697
            ?wxID_OK -> {ok, wxFileDialog:getPath(Dialog)}
 
698
        end,
 
699
    wxFileDialog:destroy(Dialog),
 
700
    Choice.