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

« back to all changes in this revision

Viewing changes to lib/reltool/src/reltool_fgraph_win.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
 
19
19
-module(reltool_fgraph_win).
95
95
add_link(Pid, {FromKey, ToKey}) -> Pid ! {add_link, {FromKey, ToKey}}.
96
96
del_link(Pid, {FromKey, ToKey}) -> Pid ! {del_link, {FromKey, ToKey}}.
97
97
 
98
 
stop(Pid, Reason) -> 
 
98
stop(Pid, Reason) ->
99
99
    Ref = erlang:monitor(process, Pid),
100
100
    Pid ! {stop, Reason},
101
101
    receive
110
110
    Me  = self(),
111
111
    Pid = spawn_link(fun() -> init([Parent, Me, Env, Options]) end),
112
112
    receive {Pid, {?MODULE, Panel}} -> {Pid,Panel} end.
113
 
    
 
113
 
114
114
init([ParentWin, Pid, Env, Options]) ->
115
115
    wx:set_env(Env),
116
 
    
 
116
 
117
117
    BReset  = wxButton:new(ParentWin, ?reset,  [{label,"Reset"}]),
118
118
    BFreeze = wxButton:new(ParentWin, ?freeze, [{label,"Freeze"}]),
119
119
    BLock   = wxButton:new(ParentWin, ?lock,   [{label,"Lock"}]),
120
120
    BUnlock = wxButton:new(ParentWin, ?unlock, [{label,"Unlock"}]),
121
121
    BDelete = wxButton:new(ParentWin, ?delete, [{label,"Delete"}]),
122
122
 
123
 
    SQ  = wxSlider:new(ParentWin, ?q_slider, ?default_q, 1, 500, [{style, ?wxVERTICAL}]),
124
 
    SL  = wxSlider:new(ParentWin, ?l_slider, ?default_l, 1, 500, [{style, ?wxVERTICAL}]),
125
 
    SK  = wxSlider:new(ParentWin, ?k_slider, ?default_k, 1, 500, [{style, ?wxVERTICAL}]),
 
123
    SQ  = wxSlider:new(ParentWin, ?q_slider, ?default_q, 1, 500,
 
124
                       [{style, ?wxVERTICAL}]),
 
125
    SL  = wxSlider:new(ParentWin, ?l_slider, ?default_l, 1, 500,
 
126
                       [{style, ?wxVERTICAL}]),
 
127
    SK  = wxSlider:new(ParentWin, ?k_slider, ?default_k, 1, 500,
 
128
                       [{style, ?wxVERTICAL}]),
126
129
    Win = wxWindow:new(ParentWin, ?wxID_ANY, Options),
127
 
    
 
130
 
128
131
    ButtonSizer = wxBoxSizer:new(?wxVERTICAL),
129
132
    wxSizer:add(ButtonSizer, BReset),
130
133
    wxSizer:add(ButtonSizer, BFreeze),
141
144
    WindowSizer = wxBoxSizer:new(?wxHORIZONTAL),
142
145
    wxSizer:add(WindowSizer, ButtonSizer, [{flag, ?wxEXPAND}, {proportion, 0}]),
143
146
    wxSizer:add(WindowSizer, Win, [{flag, ?wxEXPAND}, {proportion, 1}]),
144
 
    
 
147
 
145
148
    wxButton:setToolTip(BReset, "Remove selection and unlock all nodes."),
146
149
    wxButton:setToolTip(BFreeze, "Start/stop redraw of screen."),
147
150
    wxButton:setToolTip(BLock, "Lock all selected nodes."),
148
151
    wxButton:setToolTip(BUnlock, "Unlock all selected nodes."),
149
152
    wxButton:setToolTip(BDelete, "Delete all selected nodes."),
150
153
 
151
 
    wxButton:setToolTip(SQ, "Control repulsive force. This can also be controlled with the mouse wheel on the canvas."),
 
154
    wxButton:setToolTip(SQ, "Control repulsive force. This can also be"
 
155
                        " controlled with the mouse wheel on the canvas."),
152
156
    wxButton:setToolTip(SL, "Control link length."),
153
157
    wxButton:setToolTip(SK, "Control attractive force. Use with care."),
154
 
    wxButton:setToolTip(Win, 
155
 
                        "Drag mouse while left mouse button is pressed to perform various operations. "
156
 
                        "Combine with control key to select. Combine with shift key to lock single node."),
 
158
    wxButton:setToolTip(Win,
 
159
                        "Drag mouse while left mouse button is pressed "
 
160
                        "to perform various operations. "
 
161
                        "Combine with control key to select. Combine "
 
162
                        "with shift key to lock single node."),
157
163
 
158
164
    wxButton:connect(BReset,  command_button_clicked),
159
165
    wxButton:connect(BFreeze, command_button_clicked),
160
166
    wxButton:connect(BLock,   command_button_clicked),
161
167
    wxButton:connect(BUnlock, command_button_clicked),
162
168
    wxButton:connect(BDelete, command_button_clicked),
163
 
 
 
169
 
164
170
    wxWindow:connect(SQ, command_slider_updated),
165
171
    wxWindow:connect(SL, command_slider_updated),
166
172
    wxWindow:connect(SK, command_slider_updated),
167
 
   
168
 
    wxWindow:connect(Win, enter_window),        
 
173
 
 
174
    wxWindow:connect(Win, enter_window),
169
175
    wxWindow:connect(Win, move),
170
176
    wxWindow:connect(Win, motion),
171
177
    wxWindow:connect(Win, mousewheel),
174
180
    wxWindow:connect(Win, left_up),
175
181
    wxWindow:connect(Win, right_down),
176
182
    wxWindow:connect(Win, paint,  [{skip, true}]),
177
 
    
 
183
 
178
184
    Pen   = wxPen:new({0,0,0}, [{width, 3}]),
179
185
    Font  = wxFont:new(12, ?wxSWISS, ?wxNORMAL, ?wxNORMAL,[]),
180
186
    Brush = wxBrush:new({0,0,0}),
182
188
    Pid ! {self(), {?MODULE, WindowSizer}},
183
189
 
184
190
    wxWindow:setFocus(Win), %% Get keyboard focus
185
 
  
 
191
 
186
192
    Vs = reltool_fgraph:new(),
187
193
    Es = reltool_fgraph:new(),
188
194
 
189
195
    Me = self(),
190
196
    Ticker = spawn_link(fun() -> ticker_init(Me) end),
191
 
    
 
197
 
192
198
    loop( #state{ parent_pid = Pid,
193
199
                  q_slider = SQ,
194
200
                  l_slider = SL,
215
221
    M  = 0.5,    % mass
216
222
    P  = {float(450 + random:uniform(100)),
217
223
          float(450 + random:uniform(100))},
218
 
    G#graph{ vs = reltool_fgraph:add(Key, #fg_v{ p = P, m = M, q = Q, color = Color}, Vs)}.
 
224
    G#graph{ vs = reltool_fgraph:add(Key,
 
225
                                     #fg_v{ p = P, m = M, q = Q, color = Color},
 
226
                                     Vs)}.
219
227
 
220
228
graph_change_node(Key, Color, G) ->
221
229
    case reltool_fgraph:get(Key, G#graph.vs) of
222
 
        undefined -> 
 
230
        undefined ->
223
231
            G;
224
232
        V ->
225
 
            G#graph{ vs = reltool_fgraph:set(Key, V#fg_v{ color = Color }, G#graph.vs)}
 
233
            G#graph{ vs = reltool_fgraph:set(Key, V#fg_v{ color = Color },
 
234
                                             G#graph.vs)}
226
235
    end.
227
236
 
228
237
graph_del_node(Key, G = #graph{ vs = Vs0, es = Es0}) ->
231
240
    G#graph{ vs = Vs, es = Es }.
232
241
 
233
242
graph_add_link(Key0, Key1, G = #graph{ es = Es}) ->
234
 
    K  = 60.0,   % attractive force 
 
243
    K  = 60.0,   % attractive force
235
244
    L  =  5.0,   % spring length
236
245
    G#graph{ es = reltool_fgraph:add({Key0, Key1}, #fg_e{ k = K, l = L}, Es) }.
237
246
 
249
258
        D = timer:now_diff(T1, T0)/1000,
250
259
        case round(40 - D) of
251
260
            Ms when Ms < 0 ->
252
 
                %io:format("ticker: wait is   0 ms [fg ~7s ms] [fps ~7s]~n", [s(D), s(1000/D)]),
 
261
                %io:format("ticker: wait is   0 ms [fg ~7s ms] [fps ~7s]~n",
 
262
                %          [s(D), s(1000/D)]),
253
263
                ticker_loop(Pid, 0);
254
264
            Ms ->
255
 
                %io:format("ticker: wait is ~3s ms [fg ~7s ms] [fps ~7s]~n", [s(Ms), s(D), s(1000/40)]),
 
265
                %io:format("ticker: wait is ~3s ms [fg ~7s ms] [fps ~7s]~n",
 
266
                %          [s(Ms), s(D), s(1000/40)]),
256
267
                ticker_loop(Pid, Ms)
257
268
        end
258
269
    end.
259
270
 
260
 
delete_edges(Es, []) -> 
 
271
delete_edges(Es, []) ->
261
272
    Es;
262
273
delete_edges(Es, [Key|Keys]) ->
263
274
    Edges = reltool_fgraph:foldl(fun
269
280
        (K, Esi) -> reltool_fgraph:del(K, Esi)
270
281
    end, Es, Edges),
271
282
    delete_edges(Es1, Keys).
272
 
    
 
283
 
273
284
 
274
285
set_charge(Q, Vs) -> % Repulsive force
275
286
    F = fun({Key, Value}) -> {Key, Value#fg_v{ q = Q}} end,
295
306
            wxSlider:setValue(S#state.k_slider, K),
296
307
            Es = set_length(L, G#graph.es),
297
308
            Es2 = set_spring(K, Es),
298
 
            
299
 
            Vs2 = reltool_fgraph:map(fun({Key, V}) ->
300
 
                                     {Key, V#fg_v{selected = false, type = dynamic, q = Q}}
301
 
                             end,
302
 
                             G#graph.vs),
303
 
 
304
 
            {Xs, Ys} = reltool_fgraph:foldl(fun({_Key, #fg_v{p = {X, Y}}}, {Xs, Ys}) ->
305
 
                                            {[X| Xs], [Y | Ys]}
306
 
                                    end,
307
 
                                    {[], []},
308
 
                                    Vs2),
 
309
 
 
310
            Vs2 =
 
311
                reltool_fgraph:map(fun({Key, V}) ->
 
312
                                           {Key, V#fg_v{selected = false,
 
313
                                                        type = dynamic,
 
314
                                                        q = Q}}
 
315
                                   end,
 
316
                                   G#graph.vs),
 
317
 
 
318
            {Xs, Ys} =
 
319
                reltool_fgraph:foldl(fun({_Key,
 
320
                                          #fg_v{p = {X, Y}}}, {Xs, Ys}) ->
 
321
                                             {[X| Xs], [Y | Ys]}
 
322
                                     end,
 
323
                                     {[], []},
 
324
                                     Vs2),
309
325
           %% io:format("Before: ~p\n", [G#graph.offset]),
310
326
            Offset =
311
327
                case length(Xs) of
312
328
                    0 ->
313
329
                        {0, 0};
314
330
                    N ->
315
 
                        MeanX = (lists:sum(Xs) / N), 
 
331
                        MeanX = (lists:sum(Xs) / N),
316
332
                        MeanY = (lists:sum(Ys) / N),
317
333
                        {SizeX, SizeY} = wxWindow:getSize(S#state.window),
318
 
                        %% io:format("Min: ~p\n", [{lists:min(Xs), lists:min(Ys)}]),
319
 
                        %% io:format("Mean: ~p\n", [{MeanX, MeanY}]),
320
 
                        %% io:format("Max: ~p\n", [{lists:max(Xs), lists:max(Ys)}]),
 
334
                        %% io:format("Min: ~p\n",
 
335
                        %%           [{lists:min(Xs), lists:min(Ys)}]),
 
336
                        %% io:format("Mean: ~p\n",
 
337
                        %%           [{MeanX, MeanY}]),
 
338
                        %% io:format("Max: ~p\n",
 
339
                        %%           [{lists:max(Xs), lists:max(Ys)}]),
321
340
                        %% io:format("Size: ~p\n", [{SizeX, SizeY}]),
322
341
                        %% {XM - (XS / 2), YM - (YS / 2)}
323
342
                        %% {0 - lists:min(Xs) + 20, 0 - lists:min(Ys) + 20}
324
343
                        {0 - MeanX + (SizeX / 2), 0 - MeanY + (SizeY / 2)}
325
344
                end,
326
345
            %% io:format("After: ~p\n", [Offset]),
327
 
            loop(S, G#graph{vs = Vs2, es = Es2, offset = Offset, offset_state = false});
 
346
            loop(S, G#graph{vs = Vs2,
 
347
                            es = Es2,
 
348
                            offset = Offset,
 
349
                            offset_state = false});
328
350
        #wx{id = ?freeze, event = #wxCommand{type=command_button_clicked}} ->
329
351
            %% Start/stop redraw of screen
330
352
            IsFrozen =
354
376
            loop(S, G#graph{ vs = Vs });
355
377
        #wx{id = ?delete, event = #wxCommand{type=command_button_clicked}} ->
356
378
            %% Delete all selected nodes
357
 
            {Vs1, Keys} = reltool_fgraph:foldl(fun
358
 
                                       ({Key, #fg_v{ selected = true}}, {Vs, Ks}) ->
359
 
                                              {reltool_fgraph:del(Key,Vs), [Key|Ks]};
360
 
                                       (_, {Vs, Ks}) -> {Vs, Ks}
 
379
            {Vs1, Keys} =
 
380
                reltool_fgraph:foldl(fun
 
381
                                         ({Key,
 
382
                                           #fg_v{ selected = true}},
 
383
                                          {Vs, Ks}) ->
 
384
                                             {reltool_fgraph:del(Key,Vs),
 
385
                                              [Key|Ks]};
 
386
                                         (_, {Vs, Ks}) ->
 
387
                                             {Vs, Ks}
361
388
                                      end, {G#graph.vs,[]}, G#graph.vs),
362
389
            Es = delete_edges(G#graph.es, Keys),
363
390
            loop(S, G#graph{ vs = Vs1, es = Es});
368
395
        #wx{id = ?move, event = #wxCommand{type=command_button_clicked}} ->
369
396
            loop(S#state{ mouse_act = ?move }, G);
370
397
 
371
 
        #wx{id = ?q_slider, event = #wxCommand{type=command_slider_updated, commandInt = Q}} ->
 
398
        #wx{id = ?q_slider, event = #wxCommand{type=command_slider_updated,
 
399
                                               commandInt = Q}} ->
372
400
            loop(S, G#graph{ vs = set_charge(Q, G#graph.vs)});
373
 
        #wx{id = ?l_slider, event = #wxCommand{type=command_slider_updated, commandInt = L}} ->
 
401
        #wx{id = ?l_slider, event = #wxCommand{type=command_slider_updated,
 
402
                                               commandInt = L}} ->
374
403
            loop(S, G#graph{ es = set_length(L, G#graph.es)});
375
 
        #wx{id = ?k_slider, event = #wxCommand{type=command_slider_updated, commandInt = K}} ->
 
404
        #wx{id = ?k_slider, event = #wxCommand{type=command_slider_updated,
 
405
                                               commandInt = K}} ->
376
406
            loop(S, G#graph{ es = set_spring(K, G#graph.es)});
377
407
        #wx{event=#wxKey{type=key_up, keyCode = 127}} -> % delete
378
408
            {Vs1, Keys} =
379
 
                reltool_fgraph:foldl(fun({Key, #fg_v{ selected = true}}, {Vs, Ks}) ->
380
 
                                     {reltool_fgraph:del(Key,Vs), [Key|Ks]};
381
 
                                (_, {Vs, Ks}) ->
382
 
                                     {Vs, Ks}
383
 
                             end,
384
 
                             {G#graph.vs,[]}, G#graph.vs),
 
409
                reltool_fgraph:foldl(fun({Key,
 
410
                                          #fg_v{ selected = true}},
 
411
                                         {Vs, Ks}) ->
 
412
                                             {reltool_fgraph:del(Key,Vs),
 
413
                                              [Key|Ks]};
 
414
                                        (_, {Vs, Ks}) ->
 
415
                                             {Vs, Ks}
 
416
                                     end,
 
417
                                     {G#graph.vs,[]}, G#graph.vs),
385
418
            Es = delete_edges(G#graph.es, Keys),
386
419
            loop(S, G#graph{ vs = Vs1, es = Es});
387
420
        #wx{event=#wxKey{type=key_up}} ->
390
423
            loop(S, G);
391
424
 
392
425
        %% mouse
393
 
        #wx{event=#wxMouse{type=left_down, shiftDown=Shift, controlDown=Ctrl, x=X, y=Y}} ->
 
426
        #wx{event=#wxMouse{type=left_down,
 
427
                           shiftDown=Shift,
 
428
                           controlDown=Ctrl,
 
429
                           x=X,
 
430
                           y=Y}} ->
394
431
            if
395
432
                Shift ->
396
433
                    loop(S, mouse_left_down_move(G, {X,Y}));
401
438
                S#state.mouse_act =:= ?select ->
402
439
                    loop(S, mouse_left_down_select(G, {X,Y}))
403
440
            end;
404
 
        #wx{event=#wxMouse{type=motion, shiftDown=Shift, controlDown=Ctrl, x=X, y=Y}} ->
 
441
        #wx{event=#wxMouse{type=motion,
 
442
                           shiftDown=Shift,
 
443
                           controlDown=Ctrl,
 
444
                           x=X,
 
445
                           y=Y}} ->
405
446
            if
406
447
                Shift ->
407
448
                    loop(S, mouse_motion_move(G, {X,Y}));
412
453
                S#state.mouse_act =:= ?select ->
413
454
                    loop(S, mouse_motion_select(G, {X,Y}))
414
455
            end;
415
 
        #wx{event=#wxMouse{type=left_up, shiftDown=Shift, controlDown=Ctrl, x=X, y=Y}} -> 
 
456
        #wx{event=#wxMouse{type=left_up,
 
457
                           shiftDown=Shift,
 
458
                           controlDown=Ctrl, x=X, y=Y}} ->
416
459
            if
417
460
                Shift ->
418
461
                    loop(S, mouse_left_up_move(G, {X,Y}, Shift));
424
467
                    loop(S, mouse_left_up_select(G, {X,Y}))
425
468
            end;
426
469
 
427
 
        #wx{event=#wxMouse{type=right_down,x=_X,y=_Y}} -> 
 
470
        #wx{event=#wxMouse{type=right_down,x=_X,y=_Y}} ->
428
471
            loop(S, G);
429
472
        %% mouse wheel
430
473
        #wx{event=#wxMouse{type=mousewheel, wheelRotation=Rotation}} ->
436
479
                Rotation < 0 ->
437
480
                    wxSlider:setValue(S#state.q_slider, Q + 4),
438
481
                    loop(S, G#graph{ vs = set_charge(Q + 4, G#graph.vs) });
439
 
                true -> 
 
482
                true ->
440
483
                    loop(S, G)
441
484
            end;
442
485
 
448
491
            redraw(S, G),
449
492
            loop(S, G);
450
493
        #wx{obj=Win,event=#wxMouse{type=enter_window}} ->
451
 
            wxWindow:setFocus(Win), 
 
494
            wxWindow:setFocus(Win),
452
495
            loop(S, G);
453
496
 
454
497
        %% Graph manipulation
465
508
 
466
509
        {Req, redraw} ->
467
510
            {SizeX, SizeY} = wxWindow:getSize(S#state.window),
468
 
            Vs = reltool_fgraph:step(G#graph.vs, G#graph.es, {SizeX/2.0 - 20.0, SizeY/2.0}),
 
511
            Vs = reltool_fgraph:step(G#graph.vs,
 
512
                                     G#graph.es,
 
513
                                     {SizeX/2.0 - 20.0, SizeY/2.0}),
469
514
            case S#state.is_frozen of
470
 
                false -> 
 
515
                false ->
471
516
                    Req ! {self(), ok};
472
517
                true ->
473
518
                    ignore
481
526
 
482
527
        Other ->
483
528
            error_logger:format("~p~p got unexpected message:\n\t~p\n",
484
 
                                [?MODULE, self(), Other]),          
 
529
                                [?MODULE, self(), Other]),
485
530
            loop(S, G)
486
531
    end.
487
532
 
494
539
        false ->
495
540
            G#graph{ offset_state = {X,Y}};
496
541
        {true, Key} ->
497
 
            V = #fg_v{ type = Type} = reltool_fgraph:get(Key, Vs), 
498
 
            G#graph{ vs = reltool_fgraph:set(Key, V#fg_v{ type = moving}, Vs), select = {node, Key, Type, X, Y} }
 
542
            V = #fg_v{ type = Type} = reltool_fgraph:get(Key, Vs),
 
543
            G#graph{ vs = reltool_fgraph:set(Key,
 
544
                                             V#fg_v{ type = moving}, Vs),
 
545
                     select = {node, Key, Type, X, Y} }
499
546
    end.
500
547
 
501
548
coord_to_key(#graph{vs = Vs, offset = {Xo, Yo}}, {X, Y}) ->
502
549
    Xr = X - Xo,
503
550
    Yr = Y - Yo,
504
 
    reltool_fgraph:foldl(fun({Key, #fg_v{ p = {Px, Py}}}, _) when abs(Px - Xr) < 10,
505
 
                                                          abs(Py - Yr) < 10 -> {true, Key};
506
 
                    (_, Out) -> Out
507
 
                 end, false, Vs).    
 
551
    reltool_fgraph:foldl(fun({Key, #fg_v{ p = {Px, Py}}}, _)
 
552
                               when abs(Px - Xr) < 10,
 
553
                                    abs(Py - Yr) < 10 ->
 
554
                                 {true, Key};
 
555
                            (_, Out) ->
 
556
                                 Out
 
557
                         end, false, Vs).
508
558
 
509
559
mouse_left_up_select(G, {_X,_Y}) ->
510
560
    case G#graph.select of
524
574
        _ ->
525
575
            G#graph{ select = none}
526
576
    end.
527
 
        
 
577
 
528
578
mouse_left_up_move(G = #graph{ select = Select, vs = Vs} = G, {X,Y}, Shift) ->
529
579
    case Select of
530
580
        {node, Key, _, X, Y} ->
543
593
        _ ->
544
594
            G#graph{ select = none, offset_state = false }
545
595
    end.
546
 
        
 
596
 
547
597
mouse_motion_select(G, {X,Y}) ->
548
598
    case G#graph.select of
549
599
        {P0, _P1} -> G#graph{ select = {P0, {X,Y}}};
557
607
    G#graph{ vs = reltool_fgraph:set(Key, V2, Vs) };
558
608
mouse_motion_move(G, {X,Y}) ->
559
609
    case G#graph.offset_state of
560
 
        {X1,Y1} -> 
 
610
        {X1,Y1} ->
561
611
            {X0, Y0} = G#graph.offset,
562
612
            G#graph{ offset_state = {X,Y},
563
613
                     offset = {X0 - (X1 - X), Y0 - (Y1 - Y)} };
564
 
            _ -> 
 
614
            _ ->
565
615
                G
566
616
    end.
567
617
 
574
624
    wxClientDC:destroy(DC0),
575
625
    ok.
576
626
 
577
 
redraw(DC, _Size, G) ->    
578
 
    wx:batch(fun() -> 
579
 
   
 
627
redraw(DC, _Size, G) ->
 
628
    wx:batch(fun() ->
 
629
 
580
630
        Pen   = G#graph.pen,
581
631
        Font  = G#graph.font,
582
632
        Brush = G#graph.brush,
587
637
        wxPen:setWidth(Pen, 1),
588
638
        wxDC:clear(DC),
589
639
 
590
 
        % draw vertices and edges 
 
640
        % draw vertices and edges
591
641
        wxPen:setColour(Pen, ?color_fg),
592
642
        wxDC:setPen(DC,Pen),
593
643
 
602
652
 
603
653
        % draw information text
604
654
        wxFont:setWeight(Font,?wxNORMAL),
605
 
        draw_text(DC, reltool_fgraph:size(G#graph.vs), reltool_fgraph:size(G#graph.es), G#graph.ke),
 
655
        draw_text(DC,
 
656
                  reltool_fgraph:'size'(G#graph.vs),
 
657
                  reltool_fgraph:'size'(G#graph.es), G#graph.ke),
606
658
        ok
607
659
    end).
608
660
 
612
664
    draw_line(DC, {X1,Y1}, {X0,Y1}, {0,0}),
613
665
    draw_line(DC, {X0,Y0}, {X0,Y1}, {0,0}),
614
666
    ok;
615
 
draw_select_box(_DC, _) -> 
 
667
draw_select_box(_DC, _) ->
616
668
    ok.
617
669
 
618
670
draw_es(DC, Vs, Es, Po, Pen, Brush) ->
619
671
    reltool_fgraph:foreach(fun
620
672
        ({{K1, K2}, _}) ->
621
 
            #fg_v{ p = P1} = reltool_fgraph:get(K1, Vs),
622
 
            #fg_v{ p = P2} = reltool_fgraph:get(K2, Vs),
 
673
            #fg_v{ p = P1} = reltool_fgraph:'get'(K1, Vs),
 
674
            #fg_v{ p = P2} = reltool_fgraph:'get'(K2, Vs),
623
675
            draw_arrow(DC, P1, P2, Po, Pen, Brush)
624
676
        end, Es).
625
677
 
650
702
    wxDC:drawPolygon(DC, Points, []).
651
703
 
652
704
draw_line(DC, {X0,Y0}, {X1, Y1}, {X, Y}) ->
653
 
    wxDC:drawLine(DC, {round(X0 + X), round(Y0 + Y)}, {round(X1 + X), round(Y1 + Y)}).
654
 
   
 
705
    wxDC:drawLine(DC,
 
706
                  {round(X0 + X), round(Y0 + Y)},
 
707
                  {round(X1 + X), round(Y1 + Y)}).
 
708
 
655
709
draw_vs(DC, Vs, {Xo, Yo}, Pen, Brush) ->
656
 
    reltool_fgraph:foreach(fun({Key, #fg_v{ p ={X, Y}, color = Color, selected = Sel}}) ->
 
710
    reltool_fgraph:foreach(fun({Key,
 
711
                                #fg_v{p ={X, Y},
 
712
                                      color = Color,
 
713
                                      selected = Sel}}) ->
657
714
                                   String = s(Key),
658
715
                                   case Sel of
659
716
                                       true ->
661
718
                                           wxBrush:setColour(Brush, ?color_bg),
662
719
                                           wxDC:setPen(DC,Pen),
663
720
                                           wxDC:setBrush(DC, Brush),
664
 
                                           SelProps = {round(X-12 + Xo), round(Y-12 + Yo), 24, 24},
665
 
                                           wxDC:drawRoundedRectangle(DC, SelProps, float(?ARC_R)),
 
721
                                           SelProps = {round(X-12 + Xo),
 
722
                                                       round(Y-12 + Yo),
 
723
                                                       24,
 
724
                                                       24},
 
725
                                           wxDC:drawRoundedRectangle(DC,
 
726
                                                                     SelProps,
 
727
                                                                     float(?ARC_R)),
666
728
                                           ok;
667
729
                                       false ->
668
730
                                           ok
669
731
                                   end,
670
732
                                   case Color of
671
 
                                       default -> 
 
733
                                       default ->
672
734
                                           wxPen:setColour(Pen, ?color_default),
673
 
                                           wxBrush:setColour(Brush, ?color_default_bg);
674
 
                                       alternate -> 
675
 
                                           wxPen:setColour(Pen, ?color_alternate),
676
 
                                           wxBrush:setColour(Brush, ?color_alternate_bg);
 
735
                                           wxBrush:setColour(Brush,
 
736
                                                             ?color_default_bg);
 
737
                                       alternate ->
 
738
                                           wxPen:setColour(Pen,
 
739
                                                           ?color_alternate),
 
740
                                           wxBrush:setColour(Brush,
 
741
                                                             ?color_alternate_bg);
677
742
                                       {FgColor, BgColor} ->
678
743
                                           wxPen:setColour(Pen, FgColor),
679
 
                                           wxBrush:setColour(Brush, BgColor);               
 
744
                                           wxBrush:setColour(Brush, BgColor);
680
745
                                       Color ->
681
746
                                           wxPen:setColour(Pen, Color),
682
747
                                           wxBrush:setColour(Brush, Color)
683
748
                                   end,
684
749
                                   wxDC:setPen(DC,Pen),
685
750
                                   wxDC:setBrush(DC, Brush),
686
 
                                   NodeProps = {round(X-8 + Xo),round(Y-8 + Yo),17,17},
687
 
                                   wxDC:drawRoundedRectangle(DC, NodeProps, float(?ARC_R)),
688
 
                                   wxDC:drawText(DC, String, {round(X + Xo), round(Y + Yo)}),
 
751
                                   NodeProps = {round(X-8 + Xo),
 
752
                                                round(Y-8 + Yo),17,17},
 
753
                                   wxDC:drawRoundedRectangle(DC,
 
754
                                                             NodeProps,
 
755
                                                             float(?ARC_R)),
 
756
                                   wxDC:drawText(DC,
 
757
                                                 String,
 
758
                                                 {round(X + Xo),
 
759
                                                  round(Y + Yo)}),
689
760
                                   ok;
690
761
                              (_) ->
691
762
                                   ok
692
 
                           end, 
 
763
                           end,
693
764
                           Vs).
694
765
 
695
766
draw_text(DC, Nvs, Nes, _KE) ->
720
791
%% %% Convert from an angle in radians to degrees
721
792
%% radians_to_degrees(Radians) ->
722
793
%%     Radians * 180 / math:pi().
723
 
%% 
 
794
%%
724
795
%% %% Convert from an angle in degrees to radians
725
796
%% degrees_to_radians(Degrees) ->
726
797
%%     Degrees * math:pi() / 180.