~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/observer/src/observer_app_wx.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2011. 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
-module(observer_app_wx).
 
19
 
 
20
-export([start_link/2]).
 
21
 
 
22
%% wx_object callbacks
 
23
-export([init/1, handle_info/2, terminate/2, code_change/3, handle_call/3,
 
24
         handle_event/2, handle_sync_event/3, handle_cast/2]).
 
25
 
 
26
-behaviour(wx_object).
 
27
-include_lib("wx/include/wx.hrl").
 
28
-include("observer_defs.hrl").
 
29
 
 
30
-record(state,
 
31
        {
 
32
          parent,
 
33
          panel,
 
34
          apps_w,
 
35
          app_w,
 
36
          paint,
 
37
          current,
 
38
          app,
 
39
          sel,
 
40
          appmon
 
41
        }).
 
42
 
 
43
-record(paint, {font, pen, brush, sel, links}).
 
44
 
 
45
-record(app, {ptree, n2p, links, dim}).
 
46
-record(box, {x,y, w,h, s1}).
 
47
-record(str, {x,y,text,pid}).
 
48
 
 
49
-define(BX_E, 10). %% Empty width between text and box
 
50
-define(BX_HE, (?BX_E div 2)).
 
51
-define(BY_E, 10). %% Empty height between text and box
 
52
-define(BY_HE, (?BY_E div 2)).
 
53
 
 
54
-define(BB_X, 16). %% Empty width between boxes
 
55
-define(BB_Y, 12). %% Empty height between boxes
 
56
 
 
57
-define(DRAWAREA, 5).
 
58
-define(ID_PROC_INFO, 101).
 
59
-define(ID_PROC_MSG,  102).
 
60
-define(ID_PROC_KILL, 103).
 
61
-define(ID_TRACE_PID, 104).
 
62
-define(ID_TRACE_NAME, 105).
 
63
-define(ID_TRACE_TREE_PIDS, 106).
 
64
-define(ID_TRACE_TREE_NAMES, 107).
 
65
 
 
66
start_link(Notebook, Parent) ->
 
67
    wx_object:start_link(?MODULE, [Notebook, Parent], []).
 
68
 
 
69
init([Notebook, Parent]) ->
 
70
    Panel = wxPanel:new(Notebook, [{size, wxWindow:getClientSize(Notebook)},
 
71
                                   {winid, 1}
 
72
                                  ]),
 
73
    Main = wxBoxSizer:new(?wxHORIZONTAL),
 
74
    Splitter = wxSplitterWindow:new(Panel, [{size, wxWindow:getClientSize(Panel)},
 
75
                                            {style, ?wxSP_LIVE_UPDATE},
 
76
                                            {id, 2}
 
77
                                           ]),
 
78
    Apps = wxListBox:new(Splitter, 3, []),
 
79
    %% Need extra panel and sizer to get correct size updates
 
80
    %% in draw area for some reason
 
81
    P2 = wxPanel:new(Splitter, [{winid, 4}]),
 
82
    Extra = wxBoxSizer:new(?wxVERTICAL),
 
83
    DrawingArea = wxScrolledWindow:new(P2, [{winid, ?DRAWAREA},
 
84
                                            {style,?wxFULL_REPAINT_ON_RESIZE}]),
 
85
    wxWindow:setBackgroundColour(DrawingArea, ?wxWHITE),
 
86
    wxWindow:setVirtualSize(DrawingArea, 800, 800),
 
87
    wxSplitterWindow:setMinimumPaneSize(Splitter,50),
 
88
    wxSizer:add(Extra, DrawingArea, [{flag, ?wxEXPAND},{proportion, 1}]),
 
89
    wxWindow:setSizer(P2, Extra),
 
90
    wxSplitterWindow:splitVertically(Splitter, Apps, P2, [{sashPosition, 150}]),
 
91
    wxWindow:setSizer(Panel, Main),
 
92
 
 
93
    wxSizer:add(Main, Splitter, [{flag, ?wxEXPAND bor ?wxALL},
 
94
                                 {proportion, 1}, {border, 5}]),
 
95
    wxWindow:setSizer(Panel, Main),
 
96
    wxListBox:connect(Apps, command_listbox_selected),
 
97
    wxPanel:connect(DrawingArea, paint, [callback]),
 
98
    wxPanel:connect(DrawingArea, size, [{skip, true}]),
 
99
    wxPanel:connect(DrawingArea, left_up),
 
100
    wxPanel:connect(DrawingArea, left_dclick),
 
101
    wxPanel:connect(DrawingArea, right_down),
 
102
 
 
103
    DefFont  = wxSystemSettings:getFont(?wxSYS_DEFAULT_GUI_FONT),
 
104
    SelCol   = wxSystemSettings:getColour(?wxSYS_COLOUR_HIGHLIGHT),
 
105
    SelBrush = wxBrush:new(SelCol),
 
106
    LinkPen  = wxPen:new(SelCol, [{width, 2}]),
 
107
    %%  GC = wxGraphicsContext:create(DrawingArea),
 
108
    %%  _Font = wxGraphicsContext:createFont(GC, DefFont),
 
109
    {Panel, #state{parent=Parent,
 
110
                   panel =Panel,
 
111
                   apps_w=Apps,
 
112
                   app_w =DrawingArea,
 
113
                   paint=#paint{font= DefFont,
 
114
                                pen=  ?wxBLACK_PEN,
 
115
                                brush=?wxLIGHT_GREY_BRUSH,
 
116
                                sel=  SelBrush,
 
117
                                links=LinkPen
 
118
                               }
 
119
                  }}.
 
120
 
 
121
setup_scrollbar(AppWin, App) ->
 
122
    setup_scrollbar(wxWindow:getClientSize(AppWin), AppWin, App).
 
123
 
 
124
setup_scrollbar({CW, CH}, AppWin, #app{dim={W0,H0}}) ->
 
125
    W = max(W0,CW),
 
126
    H = max(H0,CH),
 
127
    PPC = 20,
 
128
    if W0 =< CW, H0 =< CH ->
 
129
            wxScrolledWindow:setScrollbars(AppWin, W, H, 1, 1);
 
130
       H0 =< CH ->
 
131
            wxScrolledWindow:setScrollbars(AppWin, PPC, H, W div PPC+1, 1);
 
132
       W0 =< CW ->
 
133
            wxScrolledWindow:setScrollbars(AppWin, W, PPC, 1, H div PPC+1);
 
134
       true ->
 
135
            wxScrolledWindow:setScrollbars(AppWin, PPC, PPC, W div PPC+1, H div PPC+1)
 
136
    end;
 
137
setup_scrollbar(_, _, undefined) -> ok.
 
138
 
 
139
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
140
 
 
141
handle_event(#wx{event=#wxCommand{type=command_listbox_selected, cmdString=AppStr}},
 
142
             State = #state{appmon=AppMon, current=Prev}) ->
 
143
    case AppStr of
 
144
        [] ->
 
145
            {noreply, State};
 
146
        _ ->
 
147
            App = list_to_atom(AppStr),
 
148
            (Prev =/= undefined) andalso appmon_info:app(AppMon, Prev, false, []),
 
149
            appmon_info:app(AppMon, App, true, []),
 
150
            {noreply, State#state{current=App}}
 
151
    end;
 
152
 
 
153
handle_event(#wx{id=Id, event=_Sz=#wxSize{size=Size}},
 
154
             State=#state{app=App, app_w=AppWin}) ->
 
155
    Id =:= ?DRAWAREA andalso setup_scrollbar(Size,AppWin,App),
 
156
    {noreply, State};
 
157
 
 
158
handle_event(#wx{event=#wxMouse{type=Type, x=X0, y=Y0}},
 
159
             S0=#state{app=#app{ptree=Tree}, app_w=AppWin}) ->
 
160
    {X,Y} = wxScrolledWindow:calcUnscrolledPosition(AppWin, X0, Y0),
 
161
    Hit   = locate_node(X,Y, [Tree]),
 
162
    State = handle_mouse_click(Hit, Type, S0),
 
163
    {noreply, State};
 
164
 
 
165
handle_event(#wx{event=#wxCommand{type=command_menu_selected}},
 
166
             State = #state{sel=undefined}) ->
 
167
    observer_lib:display_info_dialog("Select process first"),
 
168
    {noreply, State};
 
169
 
 
170
handle_event(#wx{id=?ID_PROC_INFO, event=#wxCommand{type=command_menu_selected}},
 
171
             State = #state{panel=Panel, sel={#box{s1=#str{pid=Pid}},_}}) ->
 
172
    observer_procinfo:start(Pid, Panel, self()),
 
173
    {noreply, State};
 
174
 
 
175
handle_event(#wx{id=?ID_PROC_MSG, event=#wxCommand{type=command_menu_selected}},
 
176
             State = #state{panel=Panel, sel={#box{s1=#str{pid=Pid}},_}}) ->
 
177
    case observer_lib:user_term(Panel, "Enter message", "") of
 
178
        cancel ->         ok;
 
179
        {ok, Term} ->     Pid ! Term;
 
180
        {error, Error} -> observer_lib:display_info_dialog(Error)
 
181
    end,
 
182
    {noreply, State};
 
183
 
 
184
handle_event(#wx{id=?ID_PROC_KILL, event=#wxCommand{type=command_menu_selected}},
 
185
             State = #state{panel=Panel, sel={#box{s1=#str{pid=Pid}},_}}) ->
 
186
    case observer_lib:user_term(Panel, "Enter Exit Reason", "") of
 
187
        cancel ->         ok;
 
188
        {ok, Term} ->     exit(Pid, Term);
 
189
        {error, Error} -> observer_lib:display_info_dialog(Error)
 
190
    end,
 
191
    {noreply, State};
 
192
 
 
193
%%% Trace api
 
194
handle_event(#wx{id=?ID_TRACE_PID, event=#wxCommand{type=command_menu_selected}},
 
195
             State = #state{sel={Box,_}}) ->
 
196
    observer_trace_wx:add_processes(observer_wx:get_tracer(), [box_to_pid(Box)]),
 
197
    {noreply, State};
 
198
handle_event(#wx{id=?ID_TRACE_NAME, event=#wxCommand{type=command_menu_selected}},
 
199
             State = #state{sel={Box,_}}) ->
 
200
    observer_trace_wx:add_processes(observer_wx:get_tracer(), [box_to_reg(Box)]),
 
201
    {noreply, State};
 
202
handle_event(#wx{id=?ID_TRACE_TREE_PIDS, event=#wxCommand{type=command_menu_selected}},
 
203
             State = #state{sel=Sel}) ->
 
204
    Get = fun(Box) -> box_to_pid(Box) end,
 
205
    observer_trace_wx:add_processes(observer_wx:get_tracer(), tree_map(Sel, Get)),
 
206
    {noreply, State};
 
207
handle_event(#wx{id=?ID_TRACE_TREE_NAMES, event=#wxCommand{type=command_menu_selected}},
 
208
             State = #state{sel=Sel}) ->
 
209
    Get = fun(Box) -> box_to_reg(Box) end,
 
210
    observer_trace_wx:add_processes(observer_wx:get_tracer(), tree_map(Sel, Get)),
 
211
    {noreply, State};
 
212
 
 
213
handle_event(Event, _State) ->
 
214
    error({unhandled_event, Event}).
 
215
 
 
216
%%%%%%%%%%
 
217
handle_sync_event(#wx{event = #wxPaint{}},_,
 
218
                  #state{app_w=DA, app=App, sel=Sel, paint=Paint}) ->
 
219
    %% PaintDC must be created in a callback to work on windows.
 
220
    DC = wxPaintDC:new(DA),
 
221
    wxScrolledWindow:doPrepareDC(DA,DC),
 
222
    %% Nothing is drawn until wxPaintDC is destroyed.
 
223
    draw(DC, App, Sel, Paint),
 
224
    wxPaintDC:destroy(DC),
 
225
    ok.
 
226
%%%%%%%%%%
 
227
handle_call(Event, From, _State) ->
 
228
    error({unhandled_call, Event, From}).
 
229
 
 
230
handle_cast(Event, _State) ->
 
231
    error({unhandled_cast, Event}).
 
232
%%%%%%%%%%
 
233
handle_info({active, Node}, State = #state{parent=Parent, current=Curr, appmon=Appmon}) ->
 
234
    create_menus(Parent, []),
 
235
    {ok, Pid} = appmon_info:start_link(Node, self(), []),
 
236
    case Appmon of
 
237
        undefined -> ok;
 
238
        Pid -> ok;
 
239
        _ -> %% Deregister me as client (and stop appmon if last)
 
240
            exit(Appmon, normal)
 
241
    end,
 
242
    appmon_info:app_ctrl(Pid, Node, true, []),
 
243
    (Curr =/= undefined) andalso appmon_info:app(Pid, Curr, true, []),
 
244
    {noreply, State#state{appmon=Pid}};
 
245
 
 
246
handle_info(not_active, State = #state{appmon=AppMon, current=Prev}) ->
 
247
    appmon_info:app_ctrl(AppMon, node(AppMon), false, []),
 
248
    (Prev =/= undefined) andalso appmon_info:app(AppMon, Prev, false, []),
 
249
    {noreply, State};
 
250
 
 
251
handle_info({delivery, Pid, app_ctrl, _, Apps0},
 
252
            State = #state{appmon=Pid, apps_w=LBox}) ->
 
253
    Apps = [atom_to_list(App) || {_, App, {_, _, _}} <- Apps0],
 
254
    wxListBox:clear(LBox),
 
255
    wxListBox:appendStrings(LBox, [App || App <- lists:sort(Apps)]),
 
256
    {noreply, State};
 
257
 
 
258
handle_info({delivery, _Pid, app, _Curr, {[], [], [], []}},
 
259
            State = #state{panel=Panel}) ->
 
260
    wxWindow:refresh(Panel),
 
261
    {noreply, State#state{app=undefined, sel=undefined}};
 
262
 
 
263
handle_info({delivery, Pid, app, Curr, AppData},
 
264
            State = #state{panel=Panel, appmon=Pid, current=Curr,
 
265
                           app_w=AppWin, paint=#paint{font=Font}}) ->
 
266
    App = build_tree(AppData, {AppWin,Font}),
 
267
    setup_scrollbar(AppWin, App),
 
268
    wxWindow:refresh(Panel),
 
269
    wxWindow:layout(Panel),
 
270
    {noreply, State#state{app=App, sel=undefined}};
 
271
 
 
272
handle_info(_Event, State) ->
 
273
    %% io:format("~p:~p: ~p~n",[?MODULE,?LINE,_Event]),
 
274
    {noreply, State}.
 
275
 
 
276
%%%%%%%%%%
 
277
terminate(_Event, _State) ->
 
278
    ok.
 
279
code_change(_, _, State) ->
 
280
    State.
 
281
 
 
282
handle_mouse_click(Node = {#box{s1=#str{pid=Pid}},_}, Type,
 
283
                   State=#state{app_w=AppWin,panel=Panel}) ->
 
284
    case Type of
 
285
        left_dclick -> observer_procinfo:start(Pid, Panel, self());
 
286
        right_down ->    popup_menu(Panel);
 
287
        _ ->           ok
 
288
    end,
 
289
    wxWindow:refresh(AppWin),
 
290
    State#state{sel=Node};
 
291
handle_mouse_click(_, _, State = #state{sel=undefined}) ->
 
292
    State;
 
293
handle_mouse_click(_, right_down, State=#state{panel=Panel}) ->
 
294
    popup_menu(Panel),
 
295
    State;
 
296
handle_mouse_click(_, _, State=#state{app_w=AppWin}) ->
 
297
    wxWindow:refresh(AppWin),
 
298
    State#state{sel=undefined}.
 
299
 
 
300
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
301
 
 
302
create_menus(Parent, _) ->
 
303
    MenuEntries =
 
304
        [{"File",
 
305
          [#create_menu{id=?ID_PROC_INFO, text="Process info"},
 
306
           #create_menu{id=?ID_PROC_MSG,  text="Send Msg"},
 
307
           #create_menu{id=?ID_PROC_KILL, text="Kill process"}
 
308
          ]},
 
309
         {"Trace",
 
310
          [#create_menu{id=?ID_TRACE_PID,  text="Trace process"},
 
311
           #create_menu{id=?ID_TRACE_NAME, text="Trace named process"},
 
312
           #create_menu{id=?ID_TRACE_TREE_PIDS,  text="Trace process tree"},
 
313
           #create_menu{id=?ID_TRACE_TREE_NAMES,  text="Trace named process tree"}
 
314
          ]}],
 
315
    observer_wx:create_menus(Parent, MenuEntries).
 
316
 
 
317
popup_menu(Panel) ->
 
318
    Menu = wxMenu:new(),
 
319
    wxMenu:append(Menu, ?ID_PROC_INFO,  "Process info"),
 
320
    wxMenu:append(Menu, ?ID_TRACE_PID,  "Trace process"),
 
321
    wxMenu:append(Menu, ?ID_TRACE_NAME, "Trace named process"),
 
322
    wxMenu:append(Menu, ?ID_TRACE_TREE_PIDS, "Trace process tree"),
 
323
    wxMenu:append(Menu, ?ID_TRACE_TREE_NAMES, "Trace named process tree"),
 
324
    wxWindow:popupMenu(Panel, Menu),
 
325
    wxMenu:destroy(Menu).
 
326
 
 
327
 
 
328
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
329
locate_node(X, _Y, [{Box=#box{x=BX}, _Chs}|_Rest])
 
330
  when X < BX ->
 
331
    {left, Box};
 
332
locate_node(X,Y, [Node={Box=#box{x=BX,y=BY,w=BW,h=BH}, _Chs}|Rest])
 
333
  when X =< (BX+BW)->
 
334
    if
 
335
        Y < BY -> {above, Box}; %% Above
 
336
        Y =< (BY+BH) -> Node;
 
337
        true -> locate_node(X,Y,Rest)
 
338
    end;
 
339
locate_node(X,Y, [{_, Chs}|Rest]) ->
 
340
    case locate_node(X,Y,Chs) of
 
341
        Node = {#box{},_} -> Node;
 
342
        _Miss ->
 
343
            locate_node(X,Y,Rest)
 
344
    end;
 
345
locate_node(_, _, []) -> false.
 
346
 
 
347
locate_box(From, [{Box=#box{s1=#str{pid=From}},_}|_]) -> Box;
 
348
locate_box(From, [{_,Chs}|Rest]) ->
 
349
    case locate_box(From, Chs) of
 
350
        Box = #box{} -> Box;
 
351
        _ -> locate_box(From, Rest)
 
352
    end;
 
353
locate_box(From, []) -> {false, From}.
 
354
 
 
355
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
356
 
 
357
build_tree({Root, P2Name, Links, XLinks0}, Font) ->
 
358
    Fam = sofs:relation_to_family(sofs:relation(Links)),
 
359
    Name2P = gb_trees:from_orddict(lists:sort([{Name,Pid} || {Pid,Name} <- P2Name])),
 
360
    Lookup = gb_trees:from_orddict(sofs:to_external(Fam)),
 
361
    {_, Tree0} = build_tree2(Root, Lookup, Name2P, Font),
 
362
    {Tree, Dim} = calc_tree_size(Tree0),
 
363
    Fetch = fun({From, To}, Acc) ->
 
364
                    try {value, ToPid} = gb_trees:lookup(To, Name2P),
 
365
                         FromPid = gb_trees:get(From, Name2P),
 
366
                         [{locate_box(FromPid, [Tree]),locate_box(ToPid, [Tree])}|Acc]
 
367
                    catch _:_ ->
 
368
                            Acc
 
369
                    end
 
370
            end,
 
371
    XLinks = lists:foldl(Fetch, [], XLinks0),
 
372
    #app{ptree=Tree, dim=Dim, links=XLinks}.
 
373
 
 
374
build_tree2(Root, Tree0, N2P, Font) ->
 
375
    case gb_trees:lookup(Root, Tree0) of
 
376
        none -> {Tree0, {box(Root, N2P, Font), []}};
 
377
        {value, Children} ->
 
378
            Tree1 = gb_trees:delete(Root, Tree0),
 
379
            {Tree, CHs} = lists:foldr(fun("port " ++_, Acc) ->
 
380
                                              Acc; %% Skip ports
 
381
                                         (Child,{T0, Acc}) ->
 
382
                                              {T, C} = build_tree2(Child, T0, N2P, Font),
 
383
                                              {T, [C|Acc]}
 
384
                                      end, {Tree1, []}, Children),
 
385
            {Tree, {box(Root, N2P, Font), CHs}}
 
386
    end.
 
387
 
 
388
calc_tree_size(Tree) ->
 
389
    Cols = calc_col_start(Tree, [0]),
 
390
    {Boxes,{W,Hs}} = calc_tree_size(Tree, Cols, ?BB_X, [?BB_Y]),
 
391
    {Boxes, {W,lists:max(Hs)}}.
 
392
 
 
393
calc_col_start({#box{w=W}, Chs}, [Max|Acc0]) ->
 
394
    Acc = if Acc0 == [] -> [0]; true -> Acc0 end,
 
395
    Depth = lists:foldl(fun(Child, MDepth) -> calc_col_start(Child, MDepth) end,
 
396
                        Acc, Chs),
 
397
    [max(W,Max)|Depth].
 
398
 
 
399
calc_tree_size({Box=#box{w=W,h=H}, []}, _, X, [Y|Ys]) ->
 
400
    {{Box#box{x=X,y=Y}, []}, {X+W+?BB_X,[Y+H+?BB_Y|Ys]}};
 
401
calc_tree_size({Box, Children}, [Col|Cols], X, [H0|Hs0]) ->
 
402
    Hs1 = calc_row_start(Children, H0, Hs0),
 
403
    StartX = X+Col+?BB_X,
 
404
    {Boxes, {W,Hs}} = calc_tree_sizes(Children, Cols, StartX, StartX, Hs1, []),
 
405
    Y = middle(Boxes, H0),
 
406
    H = Y+Box#box.h+?BB_Y,
 
407
    {{Box#box{x=X,y=Y}, Boxes}, {W,[H|Hs]}}.
 
408
 
 
409
calc_tree_sizes([Child|Chs], Cols, X0, W0, Hs0, Acc) ->
 
410
    {Tree, {W,Hs}} = calc_tree_size(Child, Cols, X0, Hs0),
 
411
    calc_tree_sizes(Chs, Cols, X0, max(W,W0), Hs, [Tree|Acc]);
 
412
calc_tree_sizes([], _, _, W,Hs, Acc) ->
 
413
    {lists:reverse(Acc), {W,Hs}}.
 
414
 
 
415
calc_row_start(Chs = [{#box{h=H},_}|_], Start, Hs0) ->
 
416
    NChs = length(Chs),
 
417
    Wanted = (H*NChs + ?BB_Y*(NChs-1)) div 2 - H div 2,
 
418
    case Hs0 of
 
419
        [] -> [max(?BB_Y, Start - Wanted)];
 
420
        [Next|Hs] ->
 
421
            [max(Next, Start - Wanted)|Hs]
 
422
    end.
 
423
 
 
424
middle([], Y) -> Y;
 
425
middle([{#box{y=Y}, _}], _) -> Y;
 
426
middle([{#box{y=Y0},_}|List], _) ->
 
427
    {#box{y=Y1},_} = lists:last(List),
 
428
    (Y0+Y1) div 2.
 
429
 
 
430
box(Str0, N2P, {Win,Font}) ->
 
431
    Pid = gb_trees:get(Str0, N2P),
 
432
    Str = if hd(Str0) =:= $< -> lists:append(io_lib:format("~w", [Pid]));
 
433
             true -> Str0
 
434
          end,
 
435
    {TW,TH, _, _} = wxWindow:getTextExtent(Win, Str, [{theFont, Font}]),
 
436
    Data = #str{text=Str, x=?BX_HE, y=?BY_HE, pid=Pid},
 
437
    %% Add pid
 
438
    #box{w=TW+?BX_E, h=TH+?BY_E, s1=Data}.
 
439
 
 
440
box_to_pid(#box{s1=#str{pid=Pid}}) -> Pid.
 
441
box_to_reg(#box{s1=#str{text=[$<|_], pid=Pid}}) -> Pid;
 
442
box_to_reg(#box{s1=#str{text=Name}}) -> list_to_atom(Name).
 
443
 
 
444
tree_map({Box, Chs}, Fun) ->
 
445
    tree_map(Chs, Fun, [Fun(Box)]).
 
446
tree_map([{Box, Chs}|Rest], Fun, Acc0) ->
 
447
    Acc = tree_map(Chs, Fun, [Fun(Box)|Acc0]),
 
448
    tree_map(Rest, Fun, Acc);
 
449
tree_map([], _ , Acc) -> Acc.
 
450
 
 
451
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
452
draw(_DC, undefined, _, _) ->
 
453
    ok;
 
454
draw(DC, #app{dim={_W,_H}, ptree=Tree, links=Links}, Sel,
 
455
     #paint{font=Font, pen=Pen, brush=Brush, links=LPen, sel=SelBrush}) ->
 
456
    %% Canvas = wxGraphicsContext:create(DC),
 
457
    %% Pen    = wxGraphicsContext:createPen(Canvas, ?wxBLACK_PEN),
 
458
    %% wxGraphicsContext:setPen(Canvas, Pen),
 
459
    %% Brush = wxGraphicsContext:createBrush(Canvas, ?wxLIGHT_GREY_BRUSH),
 
460
    %% wxGraphicsContext:setBrush(Canvas, Brush),
 
461
    %% Font  = wxGraphicsContext:createFont(Canvas, wxSystemSettings:getFont(?wxSYS_DEFAULT_GUI_FONT)),
 
462
    %% wxGraphicsContext:setFont(Canvas, Font),
 
463
    %% draw_tree(Tree, Canvas).
 
464
    wxDC:setPen(DC, LPen),
 
465
    [draw_xlink(Link, DC) || Link <- Links],
 
466
    wxDC:setPen(DC, Pen),
 
467
    %% wxDC:drawRectangle(DC, {2,2}, {W-2,H-2}), %% DEBUG
 
468
    wxDC:setBrush(DC, Brush),
 
469
    wxDC:setFont(DC, Font),
 
470
    draw_tree(Tree, root, DC),
 
471
    case Sel of
 
472
        undefined -> ok;
 
473
        {#box{x=X,y=Y,w=W,h=H,s1=Str1}, _} ->
 
474
            wxDC:setBrush(DC, SelBrush),
 
475
            wxDC:drawRoundedRectangle(DC, {X-1,Y-1}, {W+2,H+2}, 8.0),
 
476
            draw_str(DC, Str1, X, Y)
 
477
    end.
 
478
 
 
479
draw_tree({Box=#box{x=X,y=Y,w=W,h=H,s1=Str1}, Chs}, Parent, DC) ->
 
480
    %%wxGraphicsContext:drawRoundedRectangle(DC, float(X), float(Y), float(W), float(H), 8.0),
 
481
    wxDC:drawRoundedRectangle(DC, {X,Y}, {W,H}, 8.0),
 
482
    draw_str(DC, Str1, X, Y),
 
483
    Dot = case Chs of
 
484
              [] -> ok;
 
485
              [{#box{x=CX0},_}|_] ->
 
486
                  CY = Y+(H div 2),
 
487
                  CX = CX0-(?BB_X div 2),
 
488
                  wxDC:drawLine(DC, {X+W, CY}, {CX, CY}),
 
489
                  {CX, CY}
 
490
          end,
 
491
    draw_link(Parent, Box, DC),
 
492
    [draw_tree(Child, Dot, DC) || Child <- Chs].
 
493
 
 
494
draw_link({CX,CY}, #box{x=X,y=Y0,h=H}, DC) ->
 
495
    Y = Y0+(H div 2),
 
496
    case Y =:= CY of
 
497
        true ->
 
498
            wxDC:drawLine(DC, {CX, CY}, {X, CY});
 
499
        false ->
 
500
            wxDC:drawLines(DC, [{CX, CY}, {CX, Y}, {X,Y}])
 
501
    end;
 
502
draw_link(_, _, _) -> ok.
 
503
 
 
504
draw_xlink({#box{x=X0, y=Y0, h=BH}, #box{x=X1, y=Y1}}, DC)
 
505
  when X0 =:= X1 ->
 
506
    draw_xlink(X0,Y0,X1,Y1,BH,DC);
 
507
draw_xlink({#box{x=X0, y=Y0, h=BH, w=BW}, #box{x=X1, y=Y1}}, DC)
 
508
  when X0 < X1 ->
 
509
    draw_xlink(X0+BW,Y0,X1,Y1,BH,DC);
 
510
draw_xlink({#box{x=X0, y=Y0, h=BH}, #box{x=X1, w=BW, y=Y1}}, DC)
 
511
  when X0 > X1 ->
 
512
    draw_xlink(X1+BW,Y1,X0,Y0,BH,DC);
 
513
draw_xlink({_From, _To}, _DC) ->
 
514
    ignore.
 
515
draw_xlink(X0, Y00, X1, Y11, BH, DC) ->
 
516
    {Y0,Y1} = if Y00 < Y11 -> {Y00+BH-6, Y11+6};
 
517
                 true -> {Y00+6, Y11+BH-6}
 
518
              end,
 
519
    wxDC:drawLines(DC, [{X0,Y0}, {X0+5,Y0}, {X1-5,Y1}, {X1,Y1}]).
 
520
 
 
521
draw_str(DC, #str{x=Sx,y=Sy, text=Text}, X, Y) ->
 
522
    %%wxGraphicsContext:drawText(DC, Text, float(Sx+X), float(Sy+Y));
 
523
    wxDC:drawText(DC, Text, {X+Sx,Y+Sy});
 
524
draw_str(_, _, _, _) -> ok.