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

« back to all changes in this revision

Viewing changes to lib/reltool/src/reltool_sys_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_sys_win).
34
34
-include_lib("wx/include/wx.hrl").
35
35
-include("reltool.hrl").
36
36
 
37
 
-record(state, 
 
37
-record(state,
38
38
        {parent_pid,
39
39
         server_pid,
40
40
         app_wins,
61
61
-define(WIN_HEIGHT, 600).
62
62
 
63
63
-define(CLOSE_ITEM, ?wxID_EXIT).    %% Use OS specific version if available
64
 
-define(ABOUT_ITEM, ?wxID_ABOUT).   %% Use OS specific 
 
64
-define(ABOUT_ITEM, ?wxID_ABOUT).   %% Use OS specific
65
65
-define(CONTENTS_ITEM, 300).
66
66
-define(APP_GRAPH_ITEM, 301).
67
67
-define(MOD_GRAPH_ITEM, 302).
100
100
%% Client
101
101
 
102
102
start_link(Opts) ->
103
 
    proc_lib:start_link(?MODULE, init, [[{parent, self()} | Opts]], infinity, []).
 
103
    proc_lib:start_link(?MODULE,
 
104
                        init,
 
105
                        [[{parent, self()} | Opts]],
 
106
                        infinity,
 
107
                        []).
104
108
 
105
109
get_server(Pid) ->
106
110
    reltool_utils:call(Pid, get_server).
146
150
                    S3 = S2#state{sys = Sys2},
147
151
                    S5 = wx:batch(fun() ->
148
152
                                          Title = atom_to_list(?APPLICATION),
149
 
                                          wxFrame:setTitle(S3#state.frame, Title),
150
 
                                          %% wxFrame:setMinSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
151
 
                                          wxStatusBar:setStatusText(S3#state.status_bar, "Done."),
 
153
                                          wxFrame:setTitle(S3#state.frame,
 
154
                                                           Title),
 
155
                                          %% wxFrame:setMinSize(Frame,
 
156
                                          %% {?WIN_WIDTH, ?WIN_HEIGHT}),
 
157
                                          wxStatusBar:setStatusText(
 
158
                                            S3#state.status_bar,
 
159
                                            "Done."),
152
160
                                          S4 = redraw_apps(S3),
153
161
                                          redraw_libs(S4)
154
162
                                  end),
182
190
    receive
183
191
        {system, From, Msg} ->
184
192
            Common = S#state.common,
185
 
            sys:handle_system_msg(Msg, From, S#state.parent_pid, ?MODULE, Common#common.sys_debug, S);
 
193
            sys:handle_system_msg(Msg,
 
194
                                  From,
 
195
                                  S#state.parent_pid,
 
196
                                  ?MODULE,
 
197
                                  Common#common.sys_debug,
 
198
                                  S);
186
199
        #wx{obj = ObjRef,
187
200
            event = #wxClose{type = close_window}} = Msg ->
188
201
            if
193
206
                    FWs = S#state.fgraph_wins,
194
207
                    case lists:keysearch(ObjRef, #fgraph_win.frame, FWs) of
195
208
                        {value, FW} ->
196
 
                            reltool_fgraph_win:stop(FW#fgraph_win.pid, shutdown),
 
209
                            reltool_fgraph_win:stop(FW#fgraph_win.pid,
 
210
                                                    shutdown),
197
211
                            wxFrame:destroy(ObjRef),
198
 
                            FWs2 = lists:keydelete(ObjRef, #fgraph_win.frame, FWs),
 
212
                            FWs2 =
 
213
                                lists:keydelete(ObjRef, #fgraph_win.frame, FWs),
199
214
                            ?MODULE:loop(S#state{fgraph_wins = FWs2});
200
215
                        false ->
201
 
                            error_logger:format("~p~p got unexpected message:\n\t~p\n",
202
 
                                                [?MODULE, self(), Msg]),                            
 
216
                            error_logger:format("~p~p got unexpected "
 
217
                                                "message:\n\t~p\n",
 
218
                                                [?MODULE, self(), Msg]),
203
219
                            ?MODULE:loop(S)
204
220
                    end
205
221
            end;
206
 
        #wx{id = ?CLOSE_ITEM, event = #wxCommand{type = command_menu_selected}, userData = main_window} ->
 
222
        #wx{id = ?CLOSE_ITEM,
 
223
            event = #wxCommand{type = command_menu_selected},
 
224
            userData = main_window} ->
207
225
            wxFrame:destroy(S#state.frame),
208
226
            exit(shutdown);
209
227
        #wx{event = #wxSize{}} = Wx ->
222
240
            ?MODULE:loop(S2);
223
241
        {call, ReplyTo, Ref, {open_app, AppName}} ->
224
242
            S2 = do_open_app(S, AppName),
225
 
            {value, #app_win{pid = AppPid}} = lists:keysearch(AppName, #app_win.name, S2#state.app_wins),
 
243
            {value, #app_win{pid = AppPid}} =
 
244
                lists:keysearch(AppName, #app_win.name, S2#state.app_wins),
226
245
            reltool_utils:reply(ReplyTo, Ref, {ok, AppPid}),
227
246
            ?MODULE:loop(S2);
228
247
        {'EXIT', Pid, Reason} when Pid =:= S#state.parent_pid ->
229
 
            [reltool_fgraph_win:stop(FW#fgraph_win.pid, Reason) || FW <- S#state.fgraph_wins],
 
248
            [reltool_fgraph_win:stop(FW#fgraph_win.pid, Reason) ||
 
249
                FW <- S#state.fgraph_wins],
230
250
            exit(Reason);
231
251
        {'EXIT', _Pid, _Reason} = Exit ->
232
 
            {FWs, AWs} = handle_child_exit(Exit, S#state.fgraph_wins, S#state.app_wins),
 
252
            {FWs, AWs} = handle_child_exit(Exit,
 
253
                                           S#state.fgraph_wins,
 
254
                                           S#state.app_wins),
233
255
            ?MODULE:loop(S#state{fgraph_wins = FWs, app_wins = AWs});
234
256
        Msg ->
235
257
            error_logger:format("~p~p got unexpected message:\n\t~p\n",
261
283
 
262
284
create_window(S) ->
263
285
    Title = lists:concat([?APPLICATION, " - starting up"]),
264
 
    Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title, [{size, {?WIN_WIDTH, ?WIN_HEIGHT}}]),
 
286
    Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title,
 
287
                        [{size, {?WIN_WIDTH, ?WIN_HEIGHT}}]),
265
288
    %%wxFrame:setSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
266
289
    %% wxFrame:setMinSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
267
290
    Bar = wxFrame:createStatusBar(Frame,[]),
306
329
    File    = wxMenu:new([]),
307
330
    Help    = wxMenu:new([]),
308
331
    wxMenuBar:append(MenuBar, File, "File" ),
309
 
    wxMenu:append(File, ?APP_GRAPH_ITEM, "Display application dependency graph" ),
310
 
    wxMenu:append(File, ?MOD_GRAPH_ITEM, "Display module dependency graph" ),
 
332
    wxMenu:append(File, ?APP_GRAPH_ITEM,
 
333
                  "Display application dependency graph" ),
 
334
    wxMenu:append(File, ?MOD_GRAPH_ITEM,
 
335
                  "Display module dependency graph" ),
311
336
    wxMenu:appendSeparator(File),
312
337
    wxMenu:append(File, ?RESET_CONFIG_ITEM, "Reset configuration to default" ),
313
338
    wxMenu:append(File, ?UNDO_CONFIG_ITEM, "Undo configuration (toggle)" ),
314
339
    wxMenu:append(File, ?LOAD_CONFIG_ITEM, "Load configuration" ),
315
340
    Save = wxMenu:new(),
316
 
    wxMenu:append(Save, ?SAVE_CONFIG_NODEF_NODER_ITEM, "Save explicit configuration  (neither defaults nor derivates)"),
317
 
    wxMenu:append(Save, ?SAVE_CONFIG_DEF_NODER_ITEM  , "Save configuration defaults  (defaults only)"),
318
 
    wxMenu:append(Save, ?SAVE_CONFIG_NODEF_DER_ITEM,   "Save configuration derivates (derivates only))"),
319
 
    wxMenu:append(Save, ?SAVE_CONFIG_DEF_DER_ITEM,     "Save extended configuration  (both defaults and derivates)"),
 
341
    wxMenu:append(Save, ?SAVE_CONFIG_NODEF_NODER_ITEM,
 
342
                  "Save explicit configuration  "
 
343
                  "(neither defaults nor derivates)"),
 
344
    wxMenu:append(Save, ?SAVE_CONFIG_DEF_NODER_ITEM,
 
345
                  "Save configuration defaults  (defaults only)"),
 
346
    wxMenu:append(Save, ?SAVE_CONFIG_NODEF_DER_ITEM,
 
347
                  "Save configuration derivates (derivates only))"),
 
348
    wxMenu:append(Save, ?SAVE_CONFIG_DEF_DER_ITEM,
 
349
                  "Save extended configuration  (both defaults and derivates)"),
320
350
 
321
351
    wxMenu:append(File, ?wxID_ANY, "Save configuration", Save),
322
352
    wxMenu:appendSeparator(File),
323
 
    wxMenu:append(File, ?GEN_REL_FILES_ITEM, "Generate rel, script and boot files" ),
 
353
    wxMenu:append(File, ?GEN_REL_FILES_ITEM,
 
354
                  "Generate rel, script and boot files" ),
324
355
    wxMenu:append(File, ?GEN_TARGET_ITEM, "Generate target system" ),
325
356
    wxMenu:appendSeparator(File),
326
357
    wxMenu:append(File, ?CLOSE_ITEM, "Close" ),
375
406
                                %% ?wxLC_SINGLE_SEL bor
376
407
                                ?wxVSCROLL},
377
408
                               {size, {Width, Height}}]),
378
 
    ToolTip = "Select application(s) or open separate application window with a double click.",
 
409
    ToolTip = "Select application(s) or open separate "
 
410
        "application window with a double click.",
379
411
    wxListCtrl:setToolTip(ListCtrl, ToolTip),
380
412
 
381
413
    %% Prep images
382
414
    reltool_utils:assign_image_list(ListCtrl),
383
 
    
 
415
 
384
416
    %% Prep column label
385
417
    ListItem  = wxListItem:new(),
386
418
    wxListItem:setAlign(ListItem, ?wxLIST_FORMAT_LEFT),
395
427
 
396
428
 
397
429
    InnerSz = wxBoxSizer:new(?wxVERTICAL),
398
 
    wxSizer:add(InnerSz, 
 
430
    wxSizer:add(InnerSz,
399
431
                ListCtrl,
400
432
                [{border, 2},
401
433
                 {flag, ?wxALL bor ?wxEXPAND},
408
440
                [{flag, ?wxEXPAND}, {proportion, 1}]),
409
441
 
410
442
    %% Subscribe on events
411
 
    wxEvtHandler:connect(ListCtrl, size, [{skip, true}, {userData, app_list_ctrl}]),
 
443
    wxEvtHandler:connect(ListCtrl, size,
 
444
                         [{skip, true}, {userData, app_list_ctrl}]),
412
445
    wxEvtHandler:connect(ListCtrl, command_list_item_activated),
413
 
    wxWindow:connect(ListCtrl, enter_window),        
 
446
    wxWindow:connect(ListCtrl, enter_window),
414
447
 
415
448
    ListCtrl.
416
449
 
423
456
    wxBitmapButton:setToolTip(Button, ToolTip),
424
457
    Options = [{userData, {app_button, Action, ListCtrl}}],
425
458
    wxEvtHandler:connect(Button, command_button_clicked, Options),
426
 
    wxSizer:add(Sizer, 
 
459
    wxSizer:add(Sizer,
427
460
                Button,
428
461
                [{border, 2},
429
462
                 {flag, ?wxALL},
439
472
            "Remove selected application(s)from whitelist.";
440
473
        blacklist_add when Label =:= ?blacklist ->
441
474
            "Remove selected application(s) from blacklist.";
442
 
        blacklist_add -> 
 
475
        blacklist_add ->
443
476
            "Add selected application(s) to blacklist.";
444
477
        blacklist_del ->
445
478
            "Remove selected application(s) from blacklist."
448
481
create_lib_page(#state{book = Book} = S) ->
449
482
    Panel = wxPanel:new(Book, []),
450
483
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
451
 
    
452
 
    Tree = wxTreeCtrl:new(Panel, [{style , ?wxTR_HAS_BUTTONS bor ?wxTR_HIDE_ROOT}]),
 
484
 
 
485
    Tree = wxTreeCtrl:new(Panel,
 
486
                          [{style , ?wxTR_HAS_BUTTONS bor ?wxTR_HIDE_ROOT}]),
453
487
    ToolTip = "Edit application sources.",
454
488
    wxBitmapButton:setToolTip(Tree, ToolTip),
455
489
 
478
512
    [append_lib(Tree, LibItem, Dir) || Dir <- Sys#sys.lib_dirs],
479
513
 
480
514
    EscriptItem = append_item(Tree, Top, "Escript files", undefined),
481
 
    EscriptData = #escript_data{file = undefined, tree = Tree, item = EscriptItem},
 
515
    EscriptData = #escript_data{file = undefined,
 
516
                                tree = Tree,
 
517
                                item = EscriptItem},
482
518
    wxTreeCtrl:setItemData(Tree,EscriptItem, EscriptData),
483
519
    [append_escript(Tree, EscriptItem, File) || File <- Sys#sys.escripts],
484
520
    wxTreeCtrl:expand(Tree, LibItem),
529
565
    Panel = wxPanel:new(Book, []),
530
566
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
531
567
    AppConds = reltool_utils:incl_conds(),
532
 
    AppBox = wxRadioBox:new(Panel, 
 
568
    AppBox = wxRadioBox:new(Panel,
533
569
                            ?wxID_ANY,
534
 
                            "Application inclusion policy", 
 
570
                            "Application inclusion policy",
535
571
                            ?wxDefaultPosition,
536
572
                            ?wxDefaultSize,
537
573
                            AppConds,
543
579
    wxEvtHandler:connect(AppBox, command_radiobox_selected,
544
580
                         [{userData, config_incl_cond}]),
545
581
    ModConds = reltool_utils:mod_conds(),
546
 
    ModBox = wxRadioBox:new(Panel, 
 
582
    ModBox = wxRadioBox:new(Panel,
547
583
                            ?wxID_ANY,
548
 
                            "Module inclusion policy", 
 
584
                            "Module inclusion policy",
549
585
                            ?wxDefaultPosition,
550
586
                            ?wxDefaultSize,
551
587
                            ModConds,
582
618
    wxButton:setToolTip(Create, "Create a new release."),
583
619
    wxButton:connect(Create, command_button_clicked, [{userData, create_rel}]),
584
620
    wxSizer:add(ButtonSizer, Create),
585
 
    
 
621
 
586
622
    Delete  = wxButton:new(Panel, ?wxID_ANY, [{label, "Delete"}]),
587
623
    wxButton:setToolTip(Delete, "Delete a release."),
588
624
    wxButton:connect(Delete, command_button_clicked, [{userData, delete_rel}]),
589
625
    wxSizer:add(ButtonSizer, Delete),
590
 
    
 
626
 
591
627
    View  = wxButton:new(Panel, ?wxID_ANY, [{label, "View script"}]),
592
628
    wxButton:setToolTip(View, "View generated script file."),
593
629
    wxButton:connect(View, command_button_clicked, [{userData, view_script}]),
594
630
    wxSizer:add(ButtonSizer, View),
595
631
 
596
632
    [add_release_page(RelBook, Rel) || Rel <- (S#state.sys)#sys.rels],
597
 
    
 
633
 
598
634
    wxSizer:add(Sizer, RelBook, [{flag, ?wxEXPAND}, {proportion, 1}]),
599
635
    wxSizer:add(Sizer, ButtonSizer, [{flag, ?wxEXPAND}]),
600
636
    wxPanel:setSizer(Panel, Sizer),
604
640
add_release_page(Book, #rel{name = RelName, rel_apps = RelApps}) ->
605
641
    Panel = wxPanel:new(Book, []),
606
642
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
607
 
    RelBox = wxRadioBox:new(Panel, 
 
643
    RelBox = wxRadioBox:new(Panel,
608
644
                            ?wxID_ANY,
609
 
                            "Applications included in the release " ++ RelName, 
 
645
                            "Applications included in the release " ++ RelName,
610
646
                            ?wxDefaultPosition,
611
647
                            ?wxDefaultSize,
612
648
                            [atom_to_list(RA#rel_app.name) || RA <- RelApps],
613
649
                            []),
614
650
    %% wxRadioBox:setSelection(RelBox, 2), % mandatory
615
 
    wxEvtHandler:connect(RelBox, command_radiobox_selected, [{userData, {config_rel_cond, RelName}}]),
616
 
    RelToolTip = "Choose which applications that shall be included in the release resource file.",
 
651
    wxEvtHandler:connect(RelBox, command_radiobox_selected,
 
652
                         [{userData, {config_rel_cond, RelName}}]),
 
653
    RelToolTip = "Choose which applications that shall "
 
654
        "be included in the release resource file.",
617
655
    wxBitmapButton:setToolTip(RelBox, RelToolTip),
618
656
 
619
657
    wxSizer:add(Sizer,
629
667
    do_open_app(S, AppName);
630
668
do_open_app(S, '') ->
631
669
    S;
632
 
do_open_app(#state{server_pid = ServerPid, common = C, app_wins = AppWins} = S, AppName) when is_atom(AppName) ->
 
670
do_open_app(#state{server_pid = ServerPid, common = C, app_wins = AppWins} = S,
 
671
            AppName)
 
672
  when is_atom(AppName) ->
633
673
    case lists:keysearch(AppName, #app_win.name, AppWins) of
634
674
        false ->
635
675
            WxEnv = wx:get_env(),
636
 
            {ok, Pid} = reltool_app_win:start_link(WxEnv, ServerPid, C, AppName),
 
676
            {ok, Pid} =
 
677
                reltool_app_win:start_link(WxEnv, ServerPid, C, AppName),
637
678
            AW = #app_win{name = AppName, pid = Pid},
638
679
            S#state{app_wins = [AW | AppWins]};
639
680
        {value, AW} ->
651
692
    wxEvtHandler:connect(PopupMenu, menu_close),
652
693
    wxWindow:popupMenu(S#state.frame, PopupMenu),
653
694
 
654
 
    Popup = #root_popup{dir = Root, choices = Choices, tree = Tree, item = Item},
 
695
    Popup = #root_popup{dir = Root,
 
696
                        choices = Choices,
 
697
                        tree = Tree,
 
698
                        item = Item},
655
699
    S#state{popup_menu = Popup}.
656
700
 
657
701
lib_popup(S, Lib, Tree, Item) ->
693
737
    wxEvtHandler:connect(PopupMenu, menu_close),
694
738
    wxWindow:popupMenu(S#state.frame, PopupMenu),
695
739
 
696
 
    Popup = #escript_popup{file = File, choices = Choices, tree = Tree, item = Item},
 
740
    Popup = #escript_popup{file = File,
 
741
                           choices = Choices,
 
742
                           tree = Tree,
 
743
                           item = Item},
697
744
    S#state{popup_menu = Popup}.
698
745
 
699
746
 
705
752
        #wxSize{type = size, size = {W, _H}} when UserData =:= app_list_ctrl ->
706
753
            wxListCtrl:setColumnWidth(ObjRef, ?APPS_APP_COL, W),
707
754
            S;
708
 
        #wxCommand{type = command_menu_selected} when Id =:= ?APP_GRAPH_ITEM ->
 
755
        #wxCommand{type = command_menu_selected}
 
756
          when Id =:= ?APP_GRAPH_ITEM ->
709
757
            update_app_graph(S);
710
 
        #wxCommand{type = command_menu_selected} when Id =:= ?MOD_GRAPH_ITEM ->
 
758
        #wxCommand{type = command_menu_selected}
 
759
          when Id =:= ?MOD_GRAPH_ITEM ->
711
760
            update_mod_graph(S);
712
 
        #wxCommand{type = command_menu_selected} when Id =:= ?RESET_CONFIG_ITEM ->
 
761
        #wxCommand{type = command_menu_selected}
 
762
          when Id =:= ?RESET_CONFIG_ITEM ->
713
763
            reset_config(S);
714
 
        #wxCommand{type = command_menu_selected} when Id =:= ?UNDO_CONFIG_ITEM ->
 
764
        #wxCommand{type = command_menu_selected}
 
765
          when Id =:= ?UNDO_CONFIG_ITEM ->
715
766
            undo_config(S);
716
 
        #wxCommand{type = command_menu_selected} when Id =:= ?LOAD_CONFIG_ITEM ->
 
767
        #wxCommand{type = command_menu_selected}
 
768
          when Id =:= ?LOAD_CONFIG_ITEM ->
717
769
            load_config(S);
718
 
        #wxCommand{type = command_menu_selected} when Id =:= ?SAVE_CONFIG_NODEF_NODER_ITEM ->
 
770
        #wxCommand{type = command_menu_selected}
 
771
          when Id =:= ?SAVE_CONFIG_NODEF_NODER_ITEM ->
719
772
            save_config(S, false, false);
720
 
        #wxCommand{type = command_menu_selected} when Id =:= ?SAVE_CONFIG_NODEF_DER_ITEM ->
 
773
        #wxCommand{type = command_menu_selected}
 
774
          when Id =:= ?SAVE_CONFIG_NODEF_DER_ITEM ->
721
775
            save_config(S, false, true);
722
776
        #wxCommand{type = command_menu_selected} when Id =:= ?SAVE_CONFIG_DEF_NODER_ITEM ->
723
777
            save_config(S, true, false);
724
 
        #wxCommand{type = command_menu_selected} when Id =:= ?SAVE_CONFIG_DEF_DER_ITEM ->
 
778
        #wxCommand{type = command_menu_selected}
 
779
          when Id =:= ?SAVE_CONFIG_DEF_DER_ITEM ->
725
780
            save_config(S, true, true);
726
 
        #wxCommand{type = command_menu_selected} when Id =:= ?GEN_REL_FILES_ITEM ->
 
781
        #wxCommand{type = command_menu_selected}
 
782
          when Id =:= ?GEN_REL_FILES_ITEM ->
727
783
            gen_rel_files(S);
728
 
        #wxCommand{type = command_menu_selected} when Id =:= ?GEN_TARGET_ITEM ->
 
784
        #wxCommand{type = command_menu_selected}
 
785
          when Id =:= ?GEN_TARGET_ITEM ->
729
786
            gen_target(S);
730
 
        #wxCommand{type = command_menu_selected} when UserData =:= main_window, Id =:= ?CONTENTS_ITEM ->
 
787
        #wxCommand{type = command_menu_selected}
 
788
          when UserData =:= main_window, Id =:= ?CONTENTS_ITEM ->
731
789
            {file, BeamFile} = code:is_loaded(?MODULE),
732
790
            EbinDir = filename:dirname(BeamFile),
733
791
            AppDir = filename:dirname(EbinDir),
735
793
            Url = "file://" ++ filename:absname(HelpFile),
736
794
            wx_misc:launchDefaultBrowser(Url),
737
795
            S;
738
 
        #wxCommand{type = command_menu_selected} when UserData =:= main_window, Id =:= ?ABOUT_ITEM ->
739
 
            AboutStr = "Reltool is a release management tool. It analyses a given"
740
 
                " Erlang/OTP installation and determines various dependencies"
741
 
                " between applications. The graphical frontend depicts the"
742
 
                " dependencies and enables interactive customization of a"
743
 
                " target system. The backend provides a batch interface"
744
 
                " for generation of customized target systems.",
745
 
            MD = wxMessageDialog:new(S#state.frame, 
 
796
        #wxCommand{type = command_menu_selected}
 
797
          when UserData =:= main_window, Id =:= ?ABOUT_ITEM ->
 
798
            AboutStr = "Reltool is a release management tool. It analyses a "
 
799
                " given Erlang/OTP installation and determines various "
 
800
                " dependencies between applications. The graphical frontend "
 
801
                " depicts the dependencies and enables interactive "
 
802
                " customization of a target system. The backend provides a "
 
803
                " batch interface for generation of customized target systems.",
 
804
            MD = wxMessageDialog:new(S#state.frame,
746
805
                                     AboutStr,
747
 
                                     [{style, ?wxOK bor ?wxICON_INFORMATION}, 
 
806
                                     [{style, ?wxOK bor ?wxICON_INFORMATION},
748
807
                                      {caption, "About Reltool"}]),
749
808
            wxMessageDialog:showModal(MD),
750
809
            wxMessageDialog:destroy(MD),
758
817
            wxWindow:setFocus(ObjRef),
759
818
            S;
760
819
        _ ->
761
 
            case wxNotebook:getPageText(S#state.book, wxNotebook:getSelection(S#state.book)) of
 
820
            case wxNotebook:getPageText(S#state.book,
 
821
                                        wxNotebook:getSelection(S#state.book)) of
762
822
                ?APP_PAGE -> handle_app_event(S, Event, ObjRef, UserData);
763
823
                ?LIB_PAGE -> handle_source_event(S, Event, ObjRef, UserData);
764
824
                ?SYS_PAGE -> handle_system_event(S, Event, ObjRef, UserData);
768
828
 
769
829
handle_popup_event(S, _Type, 0, _ObjRef, _UserData, _Str) ->
770
830
    S#state{popup_menu = undefined};
771
 
handle_popup_event(#state{popup_menu = #root_popup{dir = OldDir, choices = Choices},
 
831
handle_popup_event(#state{popup_menu = #root_popup{dir = OldDir,
 
832
                                                   choices = Choices},
772
833
                          sys = Sys} = S,
773
834
                   _Type, Pos, _ObjRef, _UserData, _Str) ->
774
835
    case lists:nth(Pos, Choices) of
775
836
        edit ->
776
837
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
777
 
            case select_dir(S#state.frame, "Change root directory", OldDir, Style) of
 
838
            case select_dir(S#state.frame,
 
839
                            "Change root directory",
 
840
                            OldDir,
 
841
                            Style) of
778
842
                {ok, NewDir} when NewDir =:= OldDir ->
779
843
                    %% Same dir.Ignore.
780
844
                    S#state{popup_menu = undefined};
785
849
                    S#state{popup_menu = undefined}
786
850
            end
787
851
    end;
788
 
handle_popup_event(#state{popup_menu = #lib_popup{dir = OldDir, choices = Choices},
 
852
handle_popup_event(#state{popup_menu = #lib_popup{dir = OldDir,
 
853
                                                  choices = Choices},
789
854
                          sys = Sys} = S,
790
855
                   _Type, Pos, _ObjRef, _UserData, _Str) ->
791
856
    case lists:nth(Pos, Choices) of
801
866
                        false ->
802
867
                            LibDirs = Sys#sys.lib_dirs ++ [NewDir],
803
868
                            Sys2 = Sys#sys{lib_dirs = LibDirs},
804
 
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
869
                            do_set_sys(S#state{popup_menu = undefined,
 
870
                                               sys = Sys2})
805
871
                    end;
806
872
                cancel ->
807
873
                    S#state{popup_menu = undefined}
808
874
                end;
809
875
        edit ->
810
876
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
811
 
            case select_dir(S#state.frame, "Change library directory", OldDir, Style) of
 
877
            case select_dir(S#state.frame,
 
878
                            "Change library directory",
 
879
                            OldDir,
 
880
                            Style) of
812
881
                {ok, NewDir} ->
813
882
                    case lists:member(NewDir, Sys#sys.lib_dirs) of
814
883
                        true ->
820
889
                                lists:splitwith(Pred, Sys#sys.lib_dirs),
821
890
                            LibDirs2 = Before ++ [NewDir | After],
822
891
                            Sys2 = Sys#sys{lib_dirs = LibDirs2},
823
 
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
892
                            do_set_sys(S#state{popup_menu = undefined,
 
893
                                               sys = Sys2})
824
894
                    end;
825
895
                cancel ->
826
896
                    S#state{popup_menu = undefined}
828
898
        delete ->
829
899
            LibDirs = Sys#sys.lib_dirs -- [OldDir],
830
900
            Sys2 = Sys#sys{lib_dirs = LibDirs},
831
 
            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})     
 
901
            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
832
902
    end;
833
 
handle_popup_event(#state{popup_menu = #escript_popup{file = OldFile, choices = Choices},
 
903
handle_popup_event(#state{popup_menu = #escript_popup{file = OldFile,
 
904
                                                      choices = Choices},
834
905
                          sys = Sys} = S,
835
906
                   _Type, Pos, _ObjRef, _UserData, _Str) ->
836
907
    case lists:nth(Pos, Choices) of
837
908
        add ->
838
 
            OldFile2 = 
 
909
            OldFile2 =
839
910
                case OldFile of
840
911
                    undefined ->
841
912
                        {ok, Cwd} = file:get_cwd(),
844
915
                        OldFile
845
916
                end,
846
917
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
847
 
            case select_file(S#state.frame, "Select an escript file to add", OldFile2, Style) of
 
918
            case select_file(S#state.frame,
 
919
                             "Select an escript file to add",
 
920
                             OldFile2,
 
921
                             Style) of
848
922
                {ok, NewFile} ->
849
923
                    case lists:member(NewFile, Sys#sys.escripts) of
850
924
                        true ->
860
934
            end;
861
935
        edit ->
862
936
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
863
 
            case select_file(S#state.frame, "Change escript file name", OldFile, Style) of
 
937
            case select_file(S#state.frame,
 
938
                             "Change escript file name",
 
939
                             OldFile,
 
940
                             Style) of
864
941
                {ok, NewFile} ->
865
942
                    case lists:member(NewFile, Sys#sys.escripts) of
866
943
                        true ->
868
945
                            S#state{popup_menu = undefined};
869
946
                        false ->
870
947
                            Pred = fun(E) -> E =/= OldFile end,
871
 
                            {Before, [_| After]} = lists:splitwith(Pred, Sys#sys.escripts),
 
948
                            {Before, [_| After]} =
 
949
                                lists:splitwith(Pred, Sys#sys.escripts),
872
950
                            Escripts2 = Before ++ [NewFile | After],
873
951
                            Sys2 = Sys#sys{escripts = Escripts2},
874
 
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
952
                            do_set_sys(S#state{popup_menu = undefined,
 
953
                                               sys = Sys2})
875
954
                    end;
876
955
                cancel ->
877
956
                    S#state{popup_menu = undefined}
879
958
        delete ->
880
959
            Escripts = Sys#sys.escripts -- [OldFile],
881
960
            Sys2 = Sys#sys{escripts = Escripts},
882
 
            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})     
 
961
            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
883
962
    end.
884
963
 
885
964
handle_system_event(#state{sys = Sys} = S,
886
 
                    #wxCommand{type = command_radiobox_selected, cmdString = Choice},
 
965
                    #wxCommand{type = command_radiobox_selected,
 
966
                               cmdString = Choice},
887
967
                    _ObjRef,
888
968
                    config_mod_cond) ->
889
969
    ModCond = reltool_utils:list_to_mod_cond(Choice),
890
970
    Sys2 = Sys#sys{mod_cond = ModCond},
891
971
    do_set_sys(S#state{sys = Sys2});
892
972
handle_system_event(#state{sys = Sys} = S,
893
 
                    #wxCommand{type = command_radiobox_selected, cmdString = Choice},
 
973
                    #wxCommand{type = command_radiobox_selected,
 
974
                               cmdString = Choice},
894
975
                    _ObjRef,
895
976
                    config_incl_cond) ->
896
977
    AppCond = reltool_utils:list_to_incl_cond(Choice),
897
978
    Sys2 = Sys#sys{incl_cond = AppCond},
898
979
    do_set_sys(S#state{sys = Sys2});
899
980
handle_system_event(S, Event, ObjRef, UserData) ->
900
 
    error_logger:format("~p~p got unexpected wx sys event to ~p with user data: ~p\n\t ~p\n",
 
981
    error_logger:format("~p~p got unexpected wx sys event to ~p "
 
982
                        "with user data: ~p\n\t ~p\n",
901
983
                        [?MODULE, self(), ObjRef, UserData, Event]),
902
984
    S.
903
985
 
905
987
    io:format("Release data: ~p\n", [UserData]),
906
988
    S.
907
989
 
908
 
handle_source_event(S, #wxTree{type = command_tree_item_activated, item = Item}, ObjRef, _UserData) ->
 
990
handle_source_event(S,
 
991
                    #wxTree{type = command_tree_item_activated,
 
992
                               item = Item},
 
993
                    ObjRef,
 
994
                    _UserData) ->
909
995
    case wxTreeCtrl:getItemData(ObjRef, Item) of
910
996
        #root_data{dir = _Dir} ->
911
997
            %% io:format("Root dialog: ~p\n", [Dir]),
921
1007
        undefined ->
922
1008
            S
923
1009
    end;
924
 
handle_source_event(S, #wxTree{type = command_tree_item_right_click, item = Item}, Tree, _UserData) ->
 
1010
handle_source_event(S,
 
1011
                    #wxTree{type = command_tree_item_right_click,
 
1012
                               item = Item},
 
1013
                    Tree,
 
1014
                    _UserData) ->
925
1015
    case wxTreeCtrl:getItemData(Tree, Item) of
926
1016
        #root_data{dir = Dir} ->
927
1017
            wx:batch(fun() -> root_popup(S, Dir, Tree, Item) end);
936
1026
            S
937
1027
    end.
938
1028
 
939
 
handle_app_event(S, #wxList{type = command_list_item_activated, itemIndex = Pos}, ListCtrl, _UserData) ->
 
1029
handle_app_event(S,
 
1030
                 #wxList{type = command_list_item_activated,
 
1031
                            itemIndex = Pos},
 
1032
                 ListCtrl,
 
1033
                 _UserData) ->
940
1034
    AppName = wxListCtrl:getItemText(ListCtrl, Pos),
941
1035
    do_open_app(S, AppName);
942
 
handle_app_event(S, #wxCommand{type = command_button_clicked}, _ObjRef, {app_button, Action, ListCtrl}) ->
 
1036
handle_app_event(S,
 
1037
                 #wxCommand{type = command_button_clicked},
 
1038
                 _ObjRef,
 
1039
                 {app_button, Action, ListCtrl}) ->
943
1040
    Items = reltool_utils:get_items(ListCtrl),
944
1041
    handle_app_button(S, Items, Action);
945
1042
handle_app_event(S, Event, ObjRef, UserData) ->
946
 
    error_logger:format("~p~p got unexpected wx app event to ~p with user data: ~p\n\t ~p\n",
 
1043
    error_logger:format("~p~p got unexpected wx app event to "
 
1044
                        "~p with user data: ~p\n\t ~p\n",
947
1045
                        [?MODULE, self(), ObjRef, UserData, Event]),
948
1046
    S.
949
1047
 
950
 
handle_app_button(#state{server_pid = ServerPid, app_wins = AppWins} = S, Items, Action) ->
 
1048
handle_app_button(#state{server_pid = ServerPid, app_wins = AppWins} = S,
 
1049
                  Items,
 
1050
                  Action) ->
951
1051
    NewApps = [move_app(S, Item, Action) || Item <- Items],
952
1052
    case reltool_server:set_apps(ServerPid, NewApps) of
953
1053
        {ok, []} ->
967
1067
    check_and_refresh(S, Status).
968
1068
 
969
1069
move_app(S, {_ItemNo, AppBase}, Action) ->
970
 
    {AppName, _Vsn} = reltool_utils:split_app_name(AppBase), 
 
1070
    {AppName, _Vsn} = reltool_utils:split_app_name(AppBase),
971
1071
    {ok, OldApp} = reltool_server:get_app(S#state.server_pid, AppName),
972
 
    AppCond = 
 
1072
    AppCond =
973
1073
        case Action of
974
1074
            whitelist_add ->
975
1075
                case OldApp#app.incl_cond of
979
1079
                end;
980
1080
            whitelist_del ->
981
1081
                undefined;
982
 
            blacklist_add -> 
 
1082
            blacklist_add ->
983
1083
                exclude;
984
1084
            blacklist_del ->
985
1085
                undefined;
986
1086
            _ ->
987
 
                error_logger:format("~p~p got unexpected app button event: ~p ~p\n",
 
1087
                error_logger:format("~p~p got unexpected app "
 
1088
                                    "button event: ~p ~p\n",
988
1089
                                    [?MODULE, self(), Action, AppBase]),
989
1090
                OldApp#app.incl_cond
990
1091
        end,
1047
1148
    ImageApps = lists:map(AddImage, Apps),
1048
1149
    Show =
1049
1150
        fun({ImageId, Text, App}, {Row, ModCount, Items}) ->
1050
 
                wxListCtrl:insertItem(ListCtrl, Row, ""), 
1051
 
                if (Row rem 2) =:= 0 -> 
1052
 
                        wxListCtrl:setItemBackgroundColour(ListCtrl, Row, {240,240,255});
 
1151
                wxListCtrl:insertItem(ListCtrl, Row, ""),
 
1152
                if (Row rem 2) =:= 0 ->
 
1153
                        wxListCtrl:setItemBackgroundColour(ListCtrl,
 
1154
                                                           Row,
 
1155
                                                           {240,240,255});
1053
1156
                   true ->
1054
1157
                        ignore
1055
1158
                end,
1056
 
                wxListCtrl:setItem(ListCtrl, Row, ?APPS_APP_COL, Text, [{imageId, ImageId}]),
1057
 
                N = length([M || M <- App#app.mods, M#mod.is_included =:= true]),
 
1159
                wxListCtrl:setItem(ListCtrl,
 
1160
                                   Row,
 
1161
                                   ?APPS_APP_COL,
 
1162
                                   Text,
 
1163
                                   [{imageId, ImageId}]),
 
1164
                N = length([M || M <- App#app.mods,
 
1165
                                 M#mod.is_included =:= true]),
1058
1166
                {Row + 1, ModCount + N, [{Row, Text} | Items]}
1059
1167
        end,
1060
1168
    {_, N, NewItems} = wx:foldl(Show, {0, 0, []}, lists:sort(ImageApps)),
1068
1176
    WhiteNames = [A#app.name || A <- WhiteApps],
1069
1177
    DerivedNames = [A#app.name || A <- DerivedApps],
1070
1178
    Nodes = WhiteNames ++ DerivedNames,
1071
 
    %% WhiteUses = [N || A <- WhiteApps, N <- A#app.uses_apps, lists:member(N, Nodes)],
1072
 
    %% DerivedUses = [N || A <- DerivedApps, N <- A#app.uses_apps, lists:member(N, Nodes)],
 
1179
    %% WhiteUses = [N || A <- WhiteApps,
 
1180
    %% N <- A#app.uses_apps, lists:member(N, Nodes)],
 
1181
    %% DerivedUses = [N || A <- DerivedApps,
 
1182
    %% N <- A#app.uses_apps, lists:member(N, Nodes)],
1073
1183
 
1074
1184
    WhiteLinks = [[A#app.name, U] || A <- WhiteApps,
1075
1185
                                     U <- A#app.uses_apps,
1078
1188
    DerivedLinks = [[A#app.name, U] || A <- DerivedApps,
1079
1189
                                       U <- A#app.uses_apps,
1080
1190
                                       U =/= A#app.name,
1081
 
                                       lists:member(U, Nodes)],    
 
1191
                                       lists:member(U, Nodes)],
1082
1192
    Links = lists:usort(WhiteLinks ++ DerivedLinks),
1083
1193
    %% io:format("Links: ~p\n", [Links]),
1084
1194
    Title = lists:concat([?APPLICATION, " - application graph"]),
1087
1197
update_mod_graph(S) ->
1088
1198
    {ok, WhiteApps} = reltool_server:get_apps(S#state.server_pid, whitelist),
1089
1199
    {ok, DerivedApps} = reltool_server:get_apps(S#state.server_pid, derived),
1090
 
    WhiteMods = lists:usort([M || A <- WhiteApps, M <- A#app.mods, M#mod.is_included =:= true]),
1091
 
    DerivedMods = lists:usort([M || A <- DerivedApps, M <- A#app.mods, M#mod.is_included =:= true]),
 
1200
    WhiteMods = lists:usort([M || A <- WhiteApps,
 
1201
                                  M <- A#app.mods,
 
1202
                                  M#mod.is_included =:= true]),
 
1203
    DerivedMods = lists:usort([M || A <- DerivedApps,
 
1204
                                    M <- A#app.mods,
 
1205
                                    M#mod.is_included =:= true]),
1092
1206
 
1093
1207
    WhiteNames = [M#mod.name || M <- WhiteMods],
1094
1208
    DerivedNames = [M#mod.name || M <- DerivedMods],
1113
1227
    Panel = wxPanel:new(Frame, []),
1114
1228
    Options = [{size, {lists:max([100, ?WIN_WIDTH - 100]), ?WIN_HEIGHT}}],
1115
1229
    {Server, Fgraph} = reltool_fgraph_win:new(Panel, Options),
1116
 
    Choose = fun(?MISSING_APP) -> alternate;
 
1230
    Choose = fun(?MISSING_APP_NAME) -> alternate;
1117
1231
                (_) -> default
1118
1232
             end,
1119
1233
    [reltool_fgraph_win:add_node(Server, N, Choose(N)) || N <- Nodes],
1141
1255
 
1142
1256
load_config(#state{status_bar = Bar, config_file = OldFile} = S) ->
1143
1257
    Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
1144
 
    case select_file(S#state.frame, "Select a file to load the configuration from", OldFile, Style) of
 
1258
    case select_file(S#state.frame,
 
1259
                     "Select a file to load the configuration from",
 
1260
                     OldFile,
 
1261
                     Style) of
1145
1262
        {ok, NewFile} ->
1146
1263
            wxStatusBar:setStatusText(Bar, "Processing libraries..."),
1147
1264
            Status = reltool_server:load_config(S#state.server_pid, NewFile),
1151
1268
    end.
1152
1269
 
1153
1270
save_config(#state{config_file = OldFile} = S, InclDefaults, InclDerivates) ->
1154
 
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT, 
1155
 
    case select_file(S#state.frame, "Select a file to save the configuration to", OldFile, Style) of
 
1271
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT,
 
1272
    case select_file(S#state.frame,
 
1273
                     "Select a file to save the configuration to",
 
1274
                     OldFile,
 
1275
                     Style) of
1156
1276
        {ok, NewFile} ->
1157
 
            Status = reltool_server:save_config(S#state.server_pid, NewFile, InclDefaults, InclDerivates),
 
1277
            Status = reltool_server:save_config(S#state.server_pid,
 
1278
                                                NewFile,
 
1279
                                                InclDefaults,
 
1280
                                                InclDerivates),
1158
1281
            check_and_refresh(S#state{config_file = NewFile}, Status);
1159
1282
        cancel ->
1160
1283
            S
1161
1284
    end.
1162
1285
 
1163
1286
gen_rel_files(#state{target_dir = OldDir} = S) ->
1164
 
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT, 
1165
 
    case select_dir(S#state.frame, "Select a directory to generate rel, script and boot files to", OldDir, Style) of
 
1287
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT,
 
1288
    case select_dir(S#state.frame,
 
1289
                    "Select a directory to generate rel, script and boot files to",
 
1290
                    OldDir,
 
1291
                    Style) of
1166
1292
        {ok, NewDir} ->
1167
1293
            Status = reltool_server:gen_rel_files(S#state.server_pid, NewDir),
1168
1294
            check_and_refresh(S, Status);
1171
1297
    end.
1172
1298
 
1173
1299
gen_target(#state{target_dir = OldDir} = S) ->
1174
 
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT, 
1175
 
    case select_dir(S#state.frame, "Select a directory to generate a target system to", OldDir, Style) of
 
1300
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT,
 
1301
    case select_dir(S#state.frame,
 
1302
                    "Select a directory to generate a target system to",
 
1303
                    OldDir,
 
1304
                    Style) of
1176
1305
        {ok, NewDir} ->
1177
1306
            Status = reltool_server:gen_target(S#state.server_pid, NewDir),
1178
1307
            check_and_refresh(S#state{target_dir = NewDir}, Status);
1186
1315
                               {defaultDir, filename:dirname(DefaultFile)},
1187
1316
                               {defaultFile, filename:basename(DefaultFile)},
1188
1317
                               {style, Style}]),
1189
 
    Choice = 
 
1318
    Choice =
1190
1319
        case wxMessageDialog:showModal(Dialog) of
1191
1320
            ?wxID_CANCEL ->  cancel;
1192
1321
            ?wxID_OK -> {ok, wxFileDialog:getPath(Dialog)}
1199
1328
                             [{title, Message},
1200
1329
                              {defaultPath, DefaultDir},
1201
1330
                              {style, Style}]),
1202
 
    Choice = 
 
1331
    Choice =
1203
1332
        case wxMessageDialog:showModal(Dialog) of
1204
1333
            ?wxID_CANCEL ->  cancel;
1205
1334
            ?wxID_OK -> {ok, wxDirDialog:getPath(Dialog)}
1229
1358
    S2 = S#state{sys = Sys},
1230
1359
    S3 = redraw_libs(S2),
1231
1360
    redraw_apps(S3).
1232
 
    
 
1361
 
1233
1362
question_dialog(Question, Details) ->
1234
1363
    %% Parent = S#state.frame,
1235
1364
    Parent = wx:typeCast(wx:null(), wxWindow),
1236
1365
    %% [{style, ?wxYES_NO bor ?wxICON_ERROR bor ?wx}]),
1237
1366
    DialogStyle = ?wxRESIZE_BORDER bor ?wxCAPTION bor ?wxSYSTEM_MENU bor
1238
1367
        ?wxMINIMIZE_BOX bor ?wxMAXIMIZE_BOX bor ?wxCLOSE_BOX,
1239
 
    Dialog = wxDialog:new(Parent, ?wxID_ANY, "Undo dialog", [{style, DialogStyle}]),
 
1368
    Dialog = wxDialog:new(Parent, ?wxID_ANY, "Undo dialog",
 
1369
                          [{style, DialogStyle}]),
1240
1370
    Color = wxWindow:getBackgroundColour(Dialog),
1241
1371
    TextStyle = ?wxTE_READONLY bor ?wxTE_MULTILINE bor ?wxHSCROLL,
1242
 
    Text1 = wxTextCtrl:new(Dialog, ?wxID_ANY, [{style, ?wxTE_READONLY bor ?wxBORDER_NONE}]),
 
1372
    Text1 = wxTextCtrl:new(Dialog, ?wxID_ANY,
 
1373
                           [{style, ?wxTE_READONLY bor ?wxBORDER_NONE}]),
1243
1374
    wxWindow:setBackgroundColour(Text1, Color),
1244
1375
    wxTextCtrl:appendText(Text1, Question),
1245
 
    Text2 = wxTextCtrl:new(Dialog, ?wxID_ANY, [{size, {600, 400}}, {style, TextStyle}]),
 
1376
    Text2 = wxTextCtrl:new(Dialog, ?wxID_ANY,
 
1377
                           [{size, {600, 400}}, {style, TextStyle}]),
1246
1378
    wxWindow:setBackgroundColour(Text2, Color),
1247
1379
    wxTextCtrl:appendText(Text2, Details),
1248
1380
    %% wxDialog:setAffirmativeId(Dialog, ?wxID_YES),
1249
1381
    %% wxDialog:setEscapeId(Dialog, ?wxID_NO),
1250
1382
    Sizer = wxBoxSizer:new(?wxVERTICAL),
1251
1383
    wxSizer:add(Sizer, Text1, [{border, 2}, {flag, ?wxEXPAND}]),
1252
 
    wxSizer:add(Sizer, Text2, [{border, 2}, {flag, ?wxEXPAND}, {proportion, 1}]),
1253
 
    ButtSizer = wxDialog:createStdDialogButtonSizer(Dialog, ?wxOK bor ?wxCANCEL),
 
1384
    wxSizer:add(Sizer, Text2, [{border, 2},
 
1385
                               {flag, ?wxEXPAND},
 
1386
                               {proportion, 1}]),
 
1387
    ButtSizer = wxDialog:createStdDialogButtonSizer(Dialog,
 
1388
                                                    ?wxOK bor ?wxCANCEL),
1254
1389
    wxSizer:add(Sizer, ButtSizer, [{border, 2}, {flag, ?wxEXPAND}]),
1255
1390
    wxPanel:setSizer(Dialog, Sizer),
1256
1391
    wxSizer:fit(Sizer, Dialog),