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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
 
 
19
-module(reltool_sys_win).
 
20
 
 
21
%% Public
 
22
-export([start/1, set_app/2, open_app/2]).
 
23
 
 
24
%% Internal
 
25
-export([init/1, loop/1]).
 
26
 
 
27
%% sys callback functions
 
28
-export([
 
29
         system_continue/3,
 
30
         system_terminate/4,
 
31
         system_code_change/4
 
32
        ]).
 
33
 
 
34
-include_lib("wx/include/wx.hrl").
 
35
-include("reltool.hrl").
 
36
 
 
37
-record(state, 
 
38
        {parent_pid,
 
39
         xref_pid,
 
40
         app_wins,
 
41
         sys,
 
42
         common,
 
43
         config_file,
 
44
         target_dir,
 
45
         boot_dir,
 
46
         frame,
 
47
         panel,
 
48
         book,
 
49
         rel_book,
 
50
         lib_tree,
 
51
         status_bar,
 
52
         popup_menu,
 
53
         source,
 
54
         whitelist,
 
55
         blacklist,
 
56
         derived,
 
57
         fgraph_wins
 
58
        }).
 
59
 
 
60
-define(WIN_WIDTH, 800).
 
61
-define(WIN_HEIGHT, 600).
 
62
 
 
63
-define(CLOSE_ITEM, ?wxID_EXIT).    %% Use OS specific version if available
 
64
-define(ABOUT_ITEM, ?wxID_ABOUT).   %% Use OS specific 
 
65
-define(CONTENTS_ITEM, 300).
 
66
-define(APP_GRAPH_ITEM, 301).
 
67
-define(MOD_GRAPH_ITEM, 302).
 
68
-define(LOAD_CONFIG_ITEM, 303).
 
69
-define(SAVE_CONFIG_ITEM, 304).
 
70
-define(UNDO_CONFIG_ITEM, 305).
 
71
-define(RESET_CONFIG_ITEM, 306).
 
72
-define(GEN_REL_FILES_ITEM, 307).
 
73
-define(GEN_TARGET_ITEM, 308).
 
74
 
 
75
-define(APP_PAGE, "Applications").
 
76
-define(LIB_PAGE, "Libraries").
 
77
-define(SYS_PAGE, "System settings").
 
78
-define(REL_PAGE, "Releases").
 
79
 
 
80
-define(APPS_APP_COL, 0).
 
81
-define(source, "Available").
 
82
-define(whitelist, "Included").
 
83
-define(blacklist, "Excluded").
 
84
-define(derived, "Derived").
 
85
 
 
86
-record(root_data, {dir}).
 
87
-record(lib_data, {dir, tree, item}).
 
88
-record(escript_data, {file, tree, item}).
 
89
-record(app_data, {name, dir}).
 
90
-record(app_win, {name, pid}).
 
91
-record(fgraph_win, {frame, pid}).
 
92
-record(root_popup, {dir, choices, tree, item}).
 
93
-record(lib_popup, {dir, choices, tree, item}).
 
94
-record(escript_popup, {file, choices, tree, item}).
 
95
 
 
96
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
97
%% Client
 
98
 
 
99
start(Opts) ->
 
100
    proc_lib:start_link(?MODULE, init, [[{parent, self()} | Opts]], infinity, []).
 
101
 
 
102
set_app(Pid, App) ->
 
103
    call(Pid, {set_app, App}).
 
104
 
 
105
open_app(Pid, AppName) ->
 
106
    call(Pid, {open_app, AppName}).
 
107
 
 
108
call(Name, Msg) when is_atom(Name) ->
 
109
    call(whereis(Name), Msg);
 
110
call(Pid, Msg) when is_pid(Pid) ->
 
111
    Ref = erlang:monitor(process, Pid),
 
112
    %% io:format("Send~p: ~p\n", [self(), Msg]),
 
113
    Pid ! {self(), Ref, Msg},
 
114
    receive
 
115
        {Ref, Reply} ->
 
116
            %% io:format("Rec~p: ~p\n", [self(), Reply]),
 
117
            erlang:demonitor(Ref, [flush]),
 
118
            Reply;
 
119
        {'DOWN', Ref, _, _, Reason} ->
 
120
            {error, Reason}
 
121
    end.
 
122
 
 
123
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
124
%% Server
 
125
 
 
126
reply(Pid, Ref, Msg) ->
 
127
    Pid ! {Ref, Msg}.
 
128
 
 
129
init(Options) ->
 
130
    try
 
131
        do_init(Options)
 
132
    catch
 
133
        error:Reason ->
 
134
            exit({Reason, erlang:get_stacktrace()})
 
135
    end.
 
136
 
 
137
do_init([{parent, Parent} | Options]) ->
 
138
    case reltool_server:start(Options) of
 
139
        {ok, XrefPid, C, Sys} ->
 
140
            process_flag(trap_exit, C#common.trap_exit),
 
141
            S = #state{parent_pid = Parent,
 
142
                       xref_pid = XrefPid,
 
143
                       common = C,
 
144
                       config_file = filename:absname("config.reltool"),
 
145
                       target_dir = filename:absname("reltool_target_dir"),
 
146
                       app_wins = [],
 
147
                       sys = Sys,
 
148
                       fgraph_wins = []},
 
149
            wx:new(),
 
150
            wx:debug(C#common.wx_debug),
 
151
            S2 = create_window(S),
 
152
 
 
153
            %% wx_misc:beginBusyCursor(),
 
154
            {ok, Sys2}  = reltool_server:get_sys(XrefPid),
 
155
            S3 = S2#state{sys = Sys2},
 
156
            S5 = wx:batch(fun() ->
 
157
                                  Title = atom_to_list(?APPLICATION),
 
158
                                  wxFrame:setTitle(S3#state.frame, Title),
 
159
                                  %% wxFrame:setMinSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
 
160
                                  wxStatusBar:setStatusText(S3#state.status_bar, "Done."),
 
161
                                  S4 = redraw_apps(S3),
 
162
                                  redraw_libs(S4)
 
163
                          end),
 
164
            %% wx_misc:endBusyCursor(),
 
165
            %% wxFrame:destroy(Frame),
 
166
            proc_lib:init_ack(S#state.parent_pid, {ok, self()}),
 
167
            loop(S5);
 
168
        {error, Reason} ->
 
169
            io:format("~p(~p): <ERROR> ~p\n", [?MODULE, ?LINE, Reason]),
 
170
            exit(Reason)
 
171
    end.
 
172
 
 
173
loop(S) ->
 
174
    receive
 
175
        {system, From, Msg} ->
 
176
            Common = S#state.common,
 
177
            sys:handle_system_msg(Msg, From, S#state.parent_pid, ?MODULE, Common#common.sys_debug, S);
 
178
        #wx{obj = ObjRef,
 
179
            event = #wxClose{type = close_window}} = Msg ->
 
180
            if
 
181
                ObjRef =:= S#state.frame ->
 
182
                    wxFrame:destroy(ObjRef),
 
183
                    exit(shutdown);
 
184
                true ->
 
185
                    FWs = S#state.fgraph_wins,
 
186
                    case lists:keysearch(ObjRef, #fgraph_win.frame, FWs) of
 
187
                        {value, FW} ->
 
188
                            reltool_fgraph_win:stop(FW#fgraph_win.pid, shutdown),
 
189
                            wxFrame:destroy(ObjRef),
 
190
                            FWs2 = lists:keydelete(ObjRef, #fgraph_win.frame, FWs),
 
191
                            ?MODULE:loop(S#state{fgraph_wins = FWs2});
 
192
                        false ->
 
193
                            error_logger:format("~p~p got unexpected message:\n\t~p\n",
 
194
                                                [?MODULE, self(), Msg]),                            
 
195
                            ?MODULE:loop(S)
 
196
                    end
 
197
            end;
 
198
        #wx{id = ?CLOSE_ITEM, event = #wxCommand{type = command_menu_selected}, userData = main_window} ->
 
199
            wxFrame:destroy(S#state.frame),
 
200
            exit(shutdown);
 
201
        #wx{event = #wxSize{}} = Wx ->
 
202
            Wx2 = reltool_utils:get_latest_resize(Wx),
 
203
            S2 = handle_event(S, Wx2),
 
204
            ?MODULE:loop(S2);
 
205
        #wx{} = Wx ->
 
206
            S2 = handle_event(S, Wx),
 
207
            ?MODULE:loop(S2);
 
208
        {ReplyTo, Ref, {set_app,  NewApp}} ->
 
209
            {ok, AnalysedApp, S2} = do_set_app(S, NewApp),
 
210
            reply(ReplyTo, Ref, {ok, AnalysedApp}),
 
211
            ?MODULE:loop(S2);
 
212
        {ReplyTo, Ref, {open_app, AppName}} ->
 
213
            S2 = do_open_app(S, AppName),
 
214
            {value, #app_win{pid = AppPid}} = lists:keysearch(AppName, #app_win.name, S2#state.app_wins),
 
215
            reply(ReplyTo, Ref, {ok, AppPid}),
 
216
            ?MODULE:loop(S2);
 
217
        {'EXIT', Pid, Reason} when Pid =:= S#state.parent_pid ->
 
218
            [reltool_fgraph_win:stop(FW#fgraph_win.pid, Reason) || FW <- S#state.fgraph_wins],
 
219
            exit(Reason);
 
220
        {'EXIT', _Pid, _Reason} = Exit ->
 
221
            {FWs, AWs} = handle_child_exit(Exit, S#state.fgraph_wins, S#state.app_wins),
 
222
            ?MODULE:loop(S#state{fgraph_wins = FWs, app_wins = AWs});
 
223
        Msg ->
 
224
            error_logger:format("~p~p got unexpected message:\n\t~p\n",
 
225
                                [?MODULE, self(), Msg]),
 
226
            ?MODULE:loop(S)
 
227
    end.
 
228
 
 
229
handle_child_exit({'EXIT', Pid, _Reason} = Exit, FWs, AWs) ->
 
230
    case lists:keymember(Pid, #fgraph_win.pid, FWs) of
 
231
        true ->
 
232
            msg_warning(Exit, forcegraph_window),
 
233
            {lists:keydelete(Pid, #fgraph_win.pid, FWs), AWs};
 
234
        false ->
 
235
            case lists:keymember(Pid, #app_win.pid, AWs) of
 
236
                true ->
 
237
                    msg_warning(Exit, application_window),
 
238
                    {FWs, lists:keydelete(Pid, #app_win.pid, AWs)};
 
239
                false ->
 
240
                    msg_warning(Exit, unknown),
 
241
                    {FWs, AWs}
 
242
            end
 
243
    end.
 
244
 
 
245
msg_warning({'EXIT', _Pid, shutdown}, Type) when Type =/= unknown ->
 
246
    ok;
 
247
msg_warning(Exit, Type) ->
 
248
    error_logger:format("~p~p got unexpected message (~p):\n\t~p\n",
 
249
                        [?MODULE, self(), Type, Exit]).
 
250
 
 
251
create_window(S) ->
 
252
    Title = lists:concat([?APPLICATION, " - starting up"]),
 
253
    Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title, [{size, {?WIN_WIDTH, ?WIN_HEIGHT}}]),
 
254
    %%wxFrame:setSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
 
255
    %% wxFrame:setMinSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
 
256
    Bar = wxFrame:createStatusBar(Frame,[]),
 
257
    wxStatusBar:setStatusText(Bar, "Processing libraries..."),
 
258
    %% Label = wxStaticText:new(Panel, ?wxID_ANY, Text, [{style, ?wxTE_READONLY}]),
 
259
    %% Sizer = wxBoxSizer:new(?wxVERTICAL),
 
260
    %% wxSizer:add(Sizer, Label, [{flag, ?wxEXPAND}, {proportion, 1}]),
 
261
    %% wxPanel:setSizer(Panel, Sizer),
 
262
    %% wxSizer:fit(Sizer, Frame),
 
263
    %% wxSizer:setSizeHints(Sizer, Frame),
 
264
 
 
265
    %% Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title, []),
 
266
    %%  Frame = S#state.frame,
 
267
    wxToolTip:setDelay(3000),
 
268
    Panel = wxPanel:new(Frame, []),
 
269
    %% Bar = wxFrame:createStatusBar(Frame,[]),
 
270
    create_menubar(Frame),
 
271
 
 
272
    Book = wxNotebook:new(Panel, ?wxID_ANY, []),
 
273
    S2 = S#state{frame = Frame, panel = Panel, book = Book, status_bar = Bar},
 
274
    S3 = lists:foldl(fun(Fun, Acc) -> Fun(Acc) end,
 
275
                     S2,
 
276
                     [
 
277
                      fun create_app_page/1,
 
278
                      fun create_lib_page/1,
 
279
                      fun create_main_release_page/1,
 
280
                      fun create_config_page/1
 
281
                     ]),
 
282
    Sizer = wxBoxSizer:new(?wxVERTICAL),
 
283
    wxSizer:add(Sizer, Book, [{flag, ?wxEXPAND}, {proportion, 1}]),
 
284
 
 
285
    wxPanel:setSizer(Panel, Sizer),
 
286
    wxSizer:fit(Sizer, Frame),
 
287
    wxSizer:setSizeHints(Sizer, Frame),
 
288
    wxFrame:connect(Frame, close_window),
 
289
 
 
290
    wxFrame:show(Frame),
 
291
    S3.
 
292
 
 
293
create_menubar(Frame) ->
 
294
    MenuBar = wxMenuBar:new(),
 
295
    File    = wxMenu:new([]),
 
296
    Help    = wxMenu:new([]),
 
297
    wxMenuBar:append(MenuBar, File, "File" ),
 
298
    wxMenu:append(File, ?APP_GRAPH_ITEM, "Display application dependency graph" ),
 
299
    wxMenu:append(File, ?MOD_GRAPH_ITEM, "Display module dependency graph" ),
 
300
    wxMenu:appendSeparator(File),
 
301
    wxMenu:append(File, ?RESET_CONFIG_ITEM, "Reset configuration to default" ),
 
302
    wxMenu:append(File, ?UNDO_CONFIG_ITEM, "Undo configuration (toggle)" ),
 
303
    wxMenu:append(File, ?LOAD_CONFIG_ITEM, "Load configuration" ),
 
304
    wxMenu:append(File, ?SAVE_CONFIG_ITEM, "Save configuration" ),
 
305
    wxMenu:appendSeparator(File),
 
306
    wxMenu:append(File, ?GEN_REL_FILES_ITEM, "Generate rel, script and boot files" ),
 
307
    wxMenu:append(File, ?GEN_TARGET_ITEM, "Generate target system" ),
 
308
    wxMenu:appendSeparator(File),
 
309
    wxMenu:append(File, ?CLOSE_ITEM, "Close" ),
 
310
    wxMenuBar:append(MenuBar, Help, "Help" ),
 
311
    wxMenu:append(Help, ?CONTENTS_ITEM, "Contents" ),
 
312
    wxMenu:append(Help, ?ABOUT_ITEM, "About" ),
 
313
    wxFrame:setMenuBar(Frame, MenuBar),
 
314
    wxEvtHandler:connect(Frame,
 
315
                         command_menu_selected,
 
316
                         [{userData, main_window}]),
 
317
    wxEvtHandler:connect(File, menu_close),
 
318
    wxEvtHandler:connect(Help, menu_close),
 
319
    MenuBar.
 
320
 
 
321
create_app_page(#state{book = Book} = S) ->
 
322
    Panel = wxPanel:new(Book, []),
 
323
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
324
 
 
325
    SourceCtrl  = create_app_list_ctrl(Panel, Sizer, ?source,
 
326
                                       whitelist_add, blacklist_add),
 
327
    wxSizer:add(Sizer,
 
328
                wxStaticLine:new(Panel, [{style, ?wxLI_VERTICAL}]),
 
329
                [{border, 2}, {flag, ?wxALL bor ?wxEXPAND}]),
 
330
    WhiteCtrl   = create_app_list_ctrl(Panel, Sizer, ?whitelist,
 
331
                                       whitelist_del, blacklist_add),
 
332
    wxSizer:add(Sizer,
 
333
                wxStaticLine:new(Panel, [{style, ?wxLI_VERTICAL}]),
 
334
                [{border, 2}, {flag, ?wxALL bor ?wxEXPAND}]),
 
335
    BlackCtrl   = create_app_list_ctrl(Panel, Sizer, ?blacklist,
 
336
                                       whitelist_add, blacklist_del),
 
337
    wxSizer:add(Sizer,
 
338
                wxStaticLine:new(Panel, [{style, ?wxLI_VERTICAL}]),
 
339
                [{border, 2}, {flag, ?wxALL bor ?wxEXPAND}]),
 
340
    DerivedCtrl = create_app_list_ctrl(Panel, Sizer, ?derived,
 
341
                                       whitelist_add, blacklist_add),
 
342
    %% S3 = redraw_apps(S2),
 
343
    wxPanel:setSizer(Panel, Sizer),
 
344
    wxNotebook:addPage(Book, Panel, ?APP_PAGE, []),
 
345
    S#state{source = SourceCtrl,
 
346
            whitelist = WhiteCtrl,
 
347
            blacklist = BlackCtrl,
 
348
            derived = DerivedCtrl}.
 
349
 
 
350
create_app_list_ctrl(Panel, OuterSz, Title, Tick, Cross) ->
 
351
    %% Create list control
 
352
    Width = lists:max([100, ?WIN_WIDTH - 40]) div 4,
 
353
    Height = lists:max([100, ?WIN_HEIGHT - 100]),
 
354
    ListCtrl = wxListCtrl:new(Panel,
 
355
                              [{style,
 
356
                                ?wxLC_REPORT bor
 
357
                                %% ?wxLC_SORT_ASCENDING bor
 
358
                                %% ?wxLC_SINGLE_SEL bor
 
359
                                ?wxVSCROLL},
 
360
                               {size, {Width, Height}}]),
 
361
    ToolTip = "Select application(s) or open separate application window with a double click.",
 
362
    wxListCtrl:setToolTip(ListCtrl, ToolTip),
 
363
 
 
364
    %% Prep images
 
365
    reltool_utils:assign_image_list(ListCtrl),
 
366
    
 
367
    %% Prep column label
 
368
    ListItem  = wxListItem:new(),
 
369
    wxListItem:setAlign(ListItem, ?wxLIST_FORMAT_LEFT),
 
370
    wxListItem:setText(ListItem, Title),
 
371
    wxListCtrl:insertColumn(ListCtrl, ?APPS_APP_COL, ListItem),
 
372
    wxListItem:destroy(ListItem),
 
373
 
 
374
    %% Create button
 
375
    ButtonSz = wxBoxSizer:new(?wxHORIZONTAL),
 
376
    create_button(Panel, ButtonSz, ListCtrl, Title, "wxART_TICK_MARK", Tick),
 
377
    create_button(Panel, ButtonSz, ListCtrl, Title, "wxART_CROSS_MARK", Cross),
 
378
 
 
379
 
 
380
    InnerSz = wxBoxSizer:new(?wxVERTICAL),
 
381
    wxSizer:add(InnerSz, 
 
382
                ListCtrl,
 
383
                [{border, 2},
 
384
                 {flag, ?wxALL bor ?wxEXPAND},
 
385
                 {proportion, 1}]),
 
386
    wxSizer:add(InnerSz,
 
387
                ButtonSz,
 
388
                [{flag, ?wxEXPAND}]),
 
389
    wxSizer:add(OuterSz,
 
390
                InnerSz,
 
391
                [{flag, ?wxEXPAND}, {proportion, 1}]),
 
392
 
 
393
    %% Subscribe on events
 
394
    wxEvtHandler:connect(ListCtrl, size, [{skip, true}, {userData, app_list_ctrl}]),
 
395
    wxEvtHandler:connect(ListCtrl, command_list_item_activated),
 
396
    wxWindow:connect(ListCtrl, enter_window),        
 
397
 
 
398
    ListCtrl.
 
399
 
 
400
%% create_button(_Panel, Sizer, _ListCtrl, _BitMapName, _Tag, undefined) ->
 
401
%%     wxSizer:addStretchSpacer(Sizer);
 
402
create_button(Panel, Sizer, ListCtrl, Title, BitMapName, Action) ->
 
403
    BitMap = wxArtProvider:getBitmap(BitMapName),
 
404
    Button = wxBitmapButton:new(Panel, ?wxID_ANY, BitMap, []),
 
405
    ToolTip = action_to_tool_tip(Title, Action),
 
406
    wxBitmapButton:setToolTip(Button, ToolTip),
 
407
    Options = [{userData, {app_button, Action, ListCtrl}}],
 
408
    wxEvtHandler:connect(Button, command_button_clicked, Options),
 
409
    wxSizer:add(Sizer, 
 
410
                Button,
 
411
                [{border, 2},
 
412
                 {flag, ?wxALL},
 
413
                 {proportion, 1}]).
 
414
 
 
415
action_to_tool_tip(Label, Action) ->
 
416
    case Action of
 
417
        whitelist_add when Label =:= ?whitelist ->
 
418
            "Remove selected application(s) from whitelist.";
 
419
        whitelist_add ->
 
420
            "Add selected application(s) to whitelist.";
 
421
        whitelist_del ->
 
422
            "Remove selected application(s)from whitelist.";
 
423
        blacklist_add when Label =:= ?blacklist ->
 
424
            "Remove selected application(s) from blacklist.";
 
425
        blacklist_add -> 
 
426
            "Add selected application(s) to blacklist.";
 
427
        blacklist_del ->
 
428
            "Remove selected application(s) from blacklist."
 
429
    end.
 
430
 
 
431
create_lib_page(#state{book = Book} = S) ->
 
432
    Panel = wxPanel:new(Book, []),
 
433
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
434
    
 
435
    Tree = wxTreeCtrl:new(Panel, [{style , ?wxTR_HAS_BUTTONS bor ?wxTR_HIDE_ROOT}]),
 
436
    ToolTip = "Edit application sources.",
 
437
    wxBitmapButton:setToolTip(Tree, ToolTip),
 
438
 
 
439
    wxFrame:connect(Tree, command_tree_item_activated),
 
440
    wxFrame:connect(Tree, command_tree_item_right_click),
 
441
 
 
442
    wxSizer:add(Sizer,
 
443
                Tree,
 
444
                [{border, 2},
 
445
                 {flag, ?wxALL bor ?wxEXPAND},
 
446
                 {proportion, 1}]),
 
447
    wxPanel:setSizer(Panel, Sizer),
 
448
    wxNotebook:addPage(Book, Panel, ?LIB_PAGE, []),
 
449
    S#state{lib_tree = Tree}.
 
450
 
 
451
redraw_libs(#state{lib_tree = Tree, sys = Sys} = S) ->
 
452
    wxTreeCtrl:deleteAllItems(Tree),
 
453
 
 
454
    Top = wxTreeCtrl:addRoot(Tree, "Sources", []),
 
455
    {ok, Erts} = reltool_server:get_app(S#state.xref_pid, erts),
 
456
    append_root(Tree, Top, Sys#sys.root_dir, Erts),
 
457
 
 
458
    LibItem = wxTreeCtrl:appendItem(Tree, Top, "Library directories", []),
 
459
    LibData = #lib_data{dir = undefined, tree = Tree, item = LibItem},
 
460
    wxTreeCtrl:setItemData(Tree, LibItem, LibData),
 
461
    [append_lib(Tree, LibItem, Dir) || Dir <- Sys#sys.lib_dirs],
 
462
 
 
463
    EscriptItem = append_item(Tree, Top, "Escript files", undefined),
 
464
    EscriptData = #escript_data{file = undefined, tree = Tree, item = EscriptItem},
 
465
    wxTreeCtrl:setItemData(Tree,EscriptItem, EscriptData),
 
466
    [append_escript(Tree, EscriptItem, File) || File <- Sys#sys.escripts],
 
467
    wxTreeCtrl:expand(Tree, LibItem),
 
468
    wxTreeCtrl:expand(Tree, EscriptItem),
 
469
    S.
 
470
 
 
471
append_root(Tree, Parent, Dir, Erts) ->
 
472
    Top = append_item(Tree, Parent, "Root directory", undefined),
 
473
    Data = #root_data{dir = Dir},
 
474
    RootItem = append_item(Tree, Top, Dir, Data),
 
475
    ErtsItem = append_item(Tree, RootItem, "erts", undefined),
 
476
    [append_app(Tree, ErtsItem, filename:basename(filename:dirname(D)), D)
 
477
     || D <- Erts#app.sorted_dirs],
 
478
    LibItem = append_item(Tree, RootItem, "lib", undefined),
 
479
    LibDir = filename:join([Dir, "lib"]),
 
480
    LibDirs = reltool_utils:lib_dirs(LibDir),
 
481
    AppDirs = lists:sort(fun reltool_utils:app_dir_test/2, LibDirs),
 
482
    [append_app(Tree, LibItem, D, LibDir) || D <- AppDirs],
 
483
    wxTreeCtrl:expand(Tree, Top),
 
484
    RootItem.
 
485
 
 
486
append_lib(Tree, Parent, Dir) ->
 
487
    Item = wxTreeCtrl:appendItem(Tree, Parent, Dir, []),
 
488
    Data = #lib_data{dir = Dir, tree = Tree, item = Item},
 
489
    wxTreeCtrl:setItemData(Tree, Item, Data),
 
490
    append_apps(Tree, Item, Dir).
 
491
 
 
492
append_apps(Tree, Item, Dir) ->
 
493
    AppDirs = lists:sort(fun reltool_utils:app_dir_test/2,
 
494
                         reltool_utils:lib_dirs(Dir)),
 
495
    [append_app(Tree, Item, D, Dir) || D <- AppDirs],
 
496
    Item.
 
497
 
 
498
append_app(Tree, Parent, Base, Dir) ->
 
499
    Data = #app_data{name = Base, dir = Dir},
 
500
    append_item(Tree, Parent, Base, Data).
 
501
 
 
502
append_escript(Tree, Parent, File) ->
 
503
    Data = #escript_data{file = File},
 
504
    append_item(Tree, Parent, File, Data).
 
505
 
 
506
append_item(Tree, Parent, Label, Data) ->
 
507
    Item = wxTreeCtrl:appendItem(Tree, Parent, Label, []),
 
508
    wxTreeCtrl:setItemData(Tree, Item, Data),
 
509
    Item.
 
510
 
 
511
create_config_page(#state{sys = Sys, book = Book} = S) ->
 
512
    Panel = wxPanel:new(Book, []),
 
513
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
514
    AppConds = reltool_utils:incl_conds(),
 
515
    AppBox = wxRadioBox:new(Panel, 
 
516
                            ?wxID_ANY,
 
517
                            "Application inclusion policy", 
 
518
                            ?wxDefaultPosition,
 
519
                            ?wxDefaultSize,
 
520
                            AppConds,
 
521
                            []),
 
522
    AppToolTip = "Choose default policy for inclusion of applications. ",
 
523
    wxBitmapButton:setToolTip(AppBox, AppToolTip),
 
524
    AppChoice = reltool_utils:incl_cond_to_index(Sys#sys.incl_cond),
 
525
    wxRadioBox:setSelection(AppBox, AppChoice),
 
526
    wxEvtHandler:connect(AppBox, command_radiobox_selected,
 
527
                         [{userData, config_incl_cond}]),
 
528
    ModConds = reltool_utils:mod_conds(),
 
529
    ModBox = wxRadioBox:new(Panel, 
 
530
                            ?wxID_ANY,
 
531
                            "Module inclusion policy", 
 
532
                            ?wxDefaultPosition,
 
533
                            ?wxDefaultSize,
 
534
                            ModConds,
 
535
                            []),
 
536
    ModToolTip = "Choose default policy for module inclusion.",
 
537
    wxBitmapButton:setToolTip(ModBox, ModToolTip),
 
538
 
 
539
    ModChoice = reltool_utils:mod_cond_to_index(Sys#sys.mod_cond),
 
540
    wxRadioBox:setSelection(ModBox, ModChoice),
 
541
    wxEvtHandler:connect(ModBox, command_radiobox_selected,
 
542
                         [{userData, config_mod_cond}]),
 
543
 
 
544
    wxSizer:add(Sizer,
 
545
                AppBox,
 
546
                [{border, 2},
 
547
                 {flag, ?wxALL bor ?wxEXPAND},
 
548
                 {proportion, 1}]),
 
549
    wxSizer:add(Sizer,
 
550
                ModBox,
 
551
                [{border, 2},
 
552
                 {flag, ?wxALL bor ?wxEXPAND},
 
553
                 {proportion, 1}]),
 
554
    wxPanel:setSizer(Panel, Sizer),
 
555
    wxNotebook:addPage(Book, Panel, ?SYS_PAGE, []),
 
556
    S.
 
557
 
 
558
create_main_release_page(#state{book = Book} = S) ->
 
559
    Panel = wxPanel:new(Book, []),
 
560
    RelBook = wxNotebook:new(Panel, ?wxID_ANY, []),
 
561
    Sizer = wxBoxSizer:new(?wxVERTICAL),
 
562
    ButtonSizer = wxBoxSizer:new(?wxHORIZONTAL),
 
563
 
 
564
    Create  = wxButton:new(Panel, ?wxID_ANY, [{label, "Create"}]),
 
565
    wxButton:setToolTip(Create, "Create a new release."),
 
566
    wxButton:connect(Create, command_button_clicked, [{userData, create_rel}]),
 
567
    wxSizer:add(ButtonSizer, Create),
 
568
    
 
569
    Delete  = wxButton:new(Panel, ?wxID_ANY, [{label, "Delete"}]),
 
570
    wxButton:setToolTip(Delete, "Delete a release."),
 
571
    wxButton:connect(Delete, command_button_clicked, [{userData, delete_rel}]),
 
572
    wxSizer:add(ButtonSizer, Delete),
 
573
    
 
574
    View  = wxButton:new(Panel, ?wxID_ANY, [{label, "View script"}]),
 
575
    wxButton:setToolTip(View, "View generated script file."),
 
576
    wxButton:connect(View, command_button_clicked, [{userData, view_script}]),
 
577
    wxSizer:add(ButtonSizer, View),
 
578
 
 
579
    [add_release_page(RelBook, Rel) || Rel <- (S#state.sys)#sys.rels],
 
580
    
 
581
    wxSizer:add(Sizer, RelBook, [{flag, ?wxEXPAND}, {proportion, 1}]),
 
582
    wxSizer:add(Sizer, ButtonSizer, [{flag, ?wxEXPAND}]),
 
583
    wxPanel:setSizer(Panel, Sizer),
 
584
    wxNotebook:addPage(Book, Panel, ?REL_PAGE, []),
 
585
    S#state{rel_book = RelBook}.
 
586
 
 
587
add_release_page(Book, #rel{name = RelName, rel_apps = RelApps}) ->
 
588
    Panel = wxPanel:new(Book, []),
 
589
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
590
    RelBox = wxRadioBox:new(Panel, 
 
591
                            ?wxID_ANY,
 
592
                            "Applications included in the release " ++ RelName, 
 
593
                            ?wxDefaultPosition,
 
594
                            ?wxDefaultSize,
 
595
                            [atom_to_list(RA#rel_app.name) || RA <- RelApps],
 
596
                            []),
 
597
    %% wxRadioBox:setSelection(RelBox, 2), % mandatory
 
598
    wxEvtHandler:connect(RelBox, command_radiobox_selected, [{userData, {config_rel_cond, RelName}}]),
 
599
    RelToolTip = "Choose which applications that shall be included in the release resource file.",
 
600
    wxBitmapButton:setToolTip(RelBox, RelToolTip),
 
601
 
 
602
    wxSizer:add(Sizer,
 
603
                RelBox,
 
604
                [{border, 2},
 
605
                 {flag, ?wxALL bor ?wxEXPAND},
 
606
                 {proportion, 1}]),
 
607
    wxPanel:setSizer(Panel, Sizer),
 
608
    wxNotebook:addPage(Book, Panel, RelName, []).
 
609
 
 
610
do_open_app(S, AppBase) when is_list(AppBase) ->
 
611
    {AppName, _AppVsn} = reltool_utils:split_app_name(AppBase),
 
612
    do_open_app(S, AppName);
 
613
do_open_app(S, '') ->
 
614
    S;
 
615
do_open_app(#state{xref_pid = Xref, common = C, app_wins = AppWins} = S, AppName) when is_atom(AppName) ->
 
616
    case lists:keysearch(AppName, #app_win.name, AppWins) of
 
617
        false ->
 
618
            WxEnv = wx:get_env(),
 
619
            {ok, Pid} = reltool_app_win:start(WxEnv, Xref, C, AppName),
 
620
            AW = #app_win{name = AppName, pid = Pid},
 
621
            S#state{app_wins = [AW | AppWins]};
 
622
        {value, AW} ->
 
623
            reltool_app_win:raise(AW#app_win.pid),
 
624
            S
 
625
    end.
 
626
 
 
627
root_popup(S, Root, Tree, Item) ->
 
628
    PopupMenu = wxMenu:new(),
 
629
    wxMenu:append(PopupMenu, 0, "Root dir"),
 
630
    wxMenu:appendSeparator(PopupMenu),
 
631
    wxMenu:append(PopupMenu, 1, "Edit"),
 
632
    Choices = [edit],
 
633
    wxEvtHandler:connect(PopupMenu, command_menu_selected),
 
634
    wxEvtHandler:connect(PopupMenu, menu_close),
 
635
    wxWindow:popupMenu(S#state.frame, PopupMenu),
 
636
 
 
637
    Popup = #root_popup{dir = Root, choices = Choices, tree = Tree, item = Item},
 
638
    S#state{popup_menu = Popup}.
 
639
 
 
640
lib_popup(S, Lib, Tree, Item) ->
 
641
    PopupMenu = wxMenu:new(),
 
642
    wxMenu:append(PopupMenu, 0, "Library dir"),
 
643
    wxMenu:appendSeparator(PopupMenu),
 
644
    wxMenu:append(PopupMenu, 1, "Add"),
 
645
    Choices =
 
646
        case wxTreeCtrl:getItemData(Tree, Item) of
 
647
            #lib_data{dir = undefined} ->
 
648
                [add];
 
649
            #lib_data{} ->
 
650
                wxMenu:append(PopupMenu, 2, "Edit"),
 
651
                wxMenu:append(PopupMenu, 3, "Delete"),
 
652
                [add, edit, delete]
 
653
        end,
 
654
    wxEvtHandler:connect(PopupMenu, command_menu_selected),
 
655
    wxEvtHandler:connect(PopupMenu, menu_close),
 
656
    wxWindow:popupMenu(S#state.frame, PopupMenu),
 
657
 
 
658
    Popup = #lib_popup{dir = Lib, choices = Choices, tree = Tree, item = Item},
 
659
    S#state{popup_menu = Popup}.
 
660
 
 
661
escript_popup(S, File, Tree, Item) ->
 
662
    PopupMenu = wxMenu:new(),
 
663
    wxMenu:append(PopupMenu, 0, "Escript file"),
 
664
    wxMenu:appendSeparator(PopupMenu),
 
665
    wxMenu:append(PopupMenu, 1, "Add"),
 
666
    Choices =
 
667
        case wxTreeCtrl:getItemData(Tree, Item) of
 
668
            #escript_data{file = undefined} ->
 
669
                [add];
 
670
            #escript_data{} ->
 
671
                wxMenu:append(PopupMenu, 2, "Edit"),
 
672
                wxMenu:append(PopupMenu, 3, "Delete"),
 
673
                [add, edit, delete]
 
674
        end,
 
675
    wxEvtHandler:connect(PopupMenu, command_menu_selected),
 
676
    wxEvtHandler:connect(PopupMenu, menu_close),
 
677
    wxWindow:popupMenu(S#state.frame, PopupMenu),
 
678
 
 
679
    Popup = #escript_popup{file = File, choices = Choices, tree = Tree, item = Item},
 
680
    S#state{popup_menu = Popup}.
 
681
 
 
682
 
 
683
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
684
 
 
685
handle_event(S, #wx{id = Id, obj= ObjRef, userData = UserData, event = Event} = _Wx) ->
 
686
    %% io:format("wx: ~p\n", [Wx]),
 
687
    case Event of
 
688
        #wxSize{type = size, size = {W, _H}} when UserData =:= app_list_ctrl ->
 
689
            wxListCtrl:setColumnWidth(ObjRef, ?APPS_APP_COL, W),
 
690
            S;
 
691
        #wxCommand{type = command_menu_selected} when Id =:= ?APP_GRAPH_ITEM ->
 
692
            update_app_graph(S);
 
693
        #wxCommand{type = command_menu_selected} when Id =:= ?MOD_GRAPH_ITEM ->
 
694
            update_mod_graph(S);
 
695
        #wxCommand{type = command_menu_selected} when Id =:= ?RESET_CONFIG_ITEM ->
 
696
            reset_config(S);
 
697
        #wxCommand{type = command_menu_selected} when Id =:= ?UNDO_CONFIG_ITEM ->
 
698
            undo_config(S);
 
699
        #wxCommand{type = command_menu_selected} when Id =:= ?LOAD_CONFIG_ITEM ->
 
700
            load_config(S);
 
701
        #wxCommand{type = command_menu_selected} when Id =:= ?SAVE_CONFIG_ITEM ->
 
702
            save_config(S);
 
703
        #wxCommand{type = command_menu_selected} when Id =:= ?GEN_REL_FILES_ITEM ->
 
704
            gen_rel_files(S);
 
705
        #wxCommand{type = command_menu_selected} when Id =:= ?GEN_TARGET_ITEM ->
 
706
            gen_target(S);
 
707
        #wxCommand{type = command_menu_selected} when UserData =:= main_window, Id =:= ?CONTENTS_ITEM ->
 
708
            {file, BeamFile} = code:is_loaded(?MODULE),
 
709
            EbinDir = filename:dirname(BeamFile),
 
710
            AppDir = filename:dirname(EbinDir),
 
711
            HelpFile = filename:join([AppDir, "doc", "html", "index.html"]),
 
712
            Url = "file://" ++ filename:absname(HelpFile),
 
713
            wx_misc:launchDefaultBrowser(Url),
 
714
            S;
 
715
        #wxCommand{type = command_menu_selected} when UserData =:= main_window, Id =:= ?ABOUT_ITEM ->
 
716
            AboutStr = "Reltool is a release management tool. It analyses a given"
 
717
                " Erlang/OTP installation and determines various dependencies"
 
718
                " between applications. The graphical frontend depicts the"
 
719
                " dependencies and enables interactive customization of a"
 
720
                " target system. The backend provides a batch interface"
 
721
                " for generation of customized target systems.",
 
722
            MD = wxMessageDialog:new(S#state.frame, 
 
723
                                     AboutStr,
 
724
                                     [{style, ?wxOK bor ?wxICON_INFORMATION}, 
 
725
                                      {caption, "About Reltool"}]),
 
726
            wxDialog:showModal(MD),
 
727
            wxDialog:destroy(MD),
 
728
            S;
 
729
        #wxMenu{type = menu_close} ->
 
730
            S#state{popup_menu = undefined};
 
731
        #wxCommand{type = command_menu_selected = Type, cmdString = Str}
 
732
        when S#state.popup_menu =/= undefined ->
 
733
            handle_popup_event(S, Type, Id, ObjRef, UserData, Str);
 
734
        _ ->
 
735
            case wxNotebook:getPageText(S#state.book, wxNotebook:getSelection(S#state.book)) of
 
736
                ?APP_PAGE -> handle_app_event(S, Event, ObjRef, UserData);
 
737
                ?LIB_PAGE -> handle_source_event(S, Event, ObjRef, UserData);
 
738
                ?SYS_PAGE -> handle_system_event(S, Event, ObjRef, UserData);
 
739
                ?REL_PAGE -> handle_release_event(S, Event, ObjRef, UserData)
 
740
            end
 
741
    end.
 
742
 
 
743
handle_popup_event(S, _Type, 0, _ObjRef, _UserData, _Str) ->
 
744
    S#state{popup_menu = undefined};
 
745
handle_popup_event(#state{popup_menu = #root_popup{dir = OldDir, choices = Choices},
 
746
                          sys = Sys} = S,
 
747
                   _Type, Pos, _ObjRef, _UserData, _Str) ->
 
748
    case lists:nth(Pos, Choices) of
 
749
        edit ->
 
750
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
 
751
            case select_dir(S#state.frame, "Edit root dir", OldDir, Style) of
 
752
                {ok, NewDir} when NewDir =:= OldDir ->
 
753
                    %% Same dir.Ignore.
 
754
                    S#state{popup_menu = undefined};
 
755
                {ok, NewDir} ->
 
756
                    Sys2 = Sys#sys{root_dir = NewDir},
 
757
                    do_set_sys(S#state{popup_menu = undefined, sys = Sys2});
 
758
                cancel ->
 
759
                    S#state{popup_menu = undefined}
 
760
            end
 
761
    end;
 
762
handle_popup_event(#state{popup_menu = #lib_popup{dir = OldDir, choices = Choices},
 
763
                          sys = Sys} = S,
 
764
                   _Type, Pos, _ObjRef, _UserData, _Str) ->
 
765
    case lists:nth(Pos, Choices) of
 
766
        add ->
 
767
            {ok, Cwd} = file:get_cwd(),
 
768
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
 
769
            case select_dir(S#state.frame, "Add new library directory", Cwd, Style) of
 
770
                {ok, NewDir} ->
 
771
                    case lists:member(NewDir, Sys#sys.lib_dirs) of
 
772
                        true ->
 
773
                            %% Ignore duplicate. Keep old.
 
774
                            S#state{popup_menu = undefined};
 
775
                        false ->
 
776
                            LibDirs = Sys#sys.lib_dirs ++ [NewDir],
 
777
                            Sys2 = Sys#sys{lib_dirs = LibDirs},
 
778
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
779
                    end;
 
780
                cancel ->
 
781
                    S#state{popup_menu = undefined}
 
782
                end;
 
783
        edit ->
 
784
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
 
785
            case select_dir(S#state.frame, "Edit library directory", OldDir, Style) of
 
786
                {ok, NewDir} ->
 
787
                    case lists:member(NewDir, Sys#sys.lib_dirs) of
 
788
                        true ->
 
789
                            %% Ignore duplicate. Keep old.
 
790
                            S#state{popup_menu = undefined};
 
791
                        false ->
 
792
                            Pred = fun(E) -> E =/= OldDir end,
 
793
                            {Before, [_| After]} =
 
794
                                lists:splitwith(Pred, Sys#sys.lib_dirs),
 
795
                            LibDirs2 = Before ++ [NewDir | After],
 
796
                            Sys2 = Sys#sys{lib_dirs = LibDirs2},
 
797
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
798
                    end;
 
799
                cancel ->
 
800
                    S#state{popup_menu = undefined}
 
801
            end;
 
802
        delete ->
 
803
            LibDirs = Sys#sys.lib_dirs -- [OldDir],
 
804
            Sys2 = Sys#sys{lib_dirs = LibDirs},
 
805
            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})     
 
806
    end;
 
807
handle_popup_event(#state{popup_menu = #escript_popup{file = OldFile, choices = Choices},
 
808
                          sys = Sys} = S,
 
809
                   _Type, Pos, _ObjRef, _UserData, _Str) ->
 
810
    case lists:nth(Pos, Choices) of
 
811
        add ->
 
812
            OldFile2 = 
 
813
                case OldFile of
 
814
                    undefined ->
 
815
                        {ok, Cwd} = file:get_cwd(),
 
816
                        filename:join([Cwd, "myEscript"]);
 
817
                    _ ->
 
818
                        OldFile
 
819
                end,
 
820
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
 
821
            case select_file(S#state.frame, "Add new escript file", OldFile2, Style) of
 
822
                {ok, NewFile} ->
 
823
                    case lists:member(NewFile, Sys#sys.escripts) of
 
824
                        true ->
 
825
                            %% Ignore duplicate. Keep old.
 
826
                            S#state{popup_menu = undefined};
 
827
                        false ->
 
828
                            Escripts = Sys#sys.escripts ++ [NewFile],
 
829
                            Sys2 = Sys#sys{escripts = Escripts},
 
830
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
831
                    end;
 
832
                cancel ->
 
833
                    S#state{popup_menu = undefined}
 
834
            end;
 
835
        edit ->
 
836
            Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
 
837
            case select_file(S#state.frame, "Edit escript file", OldFile, Style) of
 
838
                {ok, NewFile} ->
 
839
                    case lists:member(NewFile, Sys#sys.escripts) of
 
840
                        true ->
 
841
                            %% Ignore duplicate. Keep old.
 
842
                            S#state{popup_menu = undefined};
 
843
                        false ->
 
844
                            Pred = fun(E) -> E =/= OldFile end,
 
845
                            {Before, [_| After]} = lists:splitwith(Pred, Sys#sys.escripts),
 
846
                            Escripts2 = Before ++ [NewFile | After],
 
847
                            Sys2 = Sys#sys{escripts = Escripts2},
 
848
                            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})
 
849
                    end;
 
850
                cancel ->
 
851
                    S#state{popup_menu = undefined}
 
852
            end;
 
853
        delete ->
 
854
            Escripts = Sys#sys.escripts -- [OldFile],
 
855
            Sys2 = Sys#sys{escripts = Escripts},
 
856
            do_set_sys(S#state{popup_menu = undefined, sys = Sys2})     
 
857
    end.
 
858
 
 
859
handle_system_event(#state{sys = Sys} = S,
 
860
                    #wxCommand{type = command_radiobox_selected, cmdString = Choice},
 
861
                    _ObjRef,
 
862
                    config_mod_cond) ->
 
863
    ModCond = reltool_utils:list_to_mod_cond(Choice),
 
864
    Sys2 = Sys#sys{mod_cond = ModCond},
 
865
    do_set_sys(S#state{sys = Sys2});
 
866
handle_system_event(#state{sys = Sys} = S,
 
867
                    #wxCommand{type = command_radiobox_selected, cmdString = Choice},
 
868
                    _ObjRef,
 
869
                    config_incl_cond) ->
 
870
    AppCond = reltool_utils:list_to_incl_cond(Choice),
 
871
    Sys2 = Sys#sys{incl_cond = AppCond},
 
872
    do_set_sys(S#state{sys = Sys2}).
 
873
 
 
874
handle_release_event(S, _Event, _ObjRef, UserData) ->
 
875
    io:format("Release: ~p\n", [UserData]),
 
876
    S.
 
877
 
 
878
handle_source_event(S, #wxTree{type = command_tree_item_activated, item = Item}, ObjRef, _UserData) ->
 
879
    case wxTreeCtrl:getItemData(ObjRef, Item) of
 
880
        #root_data{dir = _Dir} ->
 
881
            %% io:format("Root dialog: ~p\n", [Dir]),
 
882
            S;
 
883
        #lib_data{dir = _Dir} ->
 
884
            %% io:format("Lib dialog: ~p\n", [Dir]),
 
885
            S;
 
886
        #escript_data{file = _File} ->
 
887
            %% io:format("Escript dialog: ~p\n", [File]),
 
888
            S;
 
889
        #app_data{name = Name} ->
 
890
            do_open_app(S, Name);
 
891
        undefined ->
 
892
            S
 
893
    end;
 
894
handle_source_event(S, #wxTree{type = command_tree_item_right_click, item = Item}, Tree, _UserData) ->
 
895
    case wxTreeCtrl:getItemData(Tree, Item) of
 
896
        #root_data{dir = Dir} ->
 
897
            wx:batch(fun() -> root_popup(S, Dir, Tree, Item) end);
 
898
        #lib_data{dir = Dir} ->
 
899
            wx:batch(fun() -> lib_popup(S, Dir, Tree, Item) end);
 
900
        #escript_data{file = File} ->
 
901
            wx:batch(fun() -> escript_popup(S, File, Tree, Item) end);
 
902
        #app_data{name = Name} ->
 
903
            io:format("App menu: ~p\n", [Name]),
 
904
            S;
 
905
        undefined ->
 
906
            S
 
907
    end.
 
908
 
 
909
handle_app_event(S, #wxList{type = command_list_item_activated, itemIndex = Pos}, ListCtrl, _UserData) ->
 
910
    AppName = wxListCtrl:getItemText(ListCtrl, Pos),
 
911
    do_open_app(S, AppName);
 
912
handle_app_event(S, #wxCommand{type = command_button_clicked}, _ObjRef, {app_button, Action, ListCtrl}) ->
 
913
    Items = reltool_utils:get_items(ListCtrl),
 
914
    handle_app_button(S, Items, Action);
 
915
handle_app_event(S, #wxMouse{type = enter_window}, ObjRef, _UserData) ->
 
916
    wxWindow:setFocus(ObjRef),
 
917
    S;
 
918
handle_app_event(S, Event, ObjRef, UserData) ->
 
919
    error_logger:format("~p~p got unexpected wx app event to ~p with user data: ~p\n\t ~p\n",
 
920
                        [?MODULE, self(), ObjRef, UserData, Event]),
 
921
    S.
 
922
 
 
923
handle_app_button(#state{xref_pid = Xref, app_wins = AppWins} = S, Items, Action) ->
 
924
    NewApps = [move_app(S, Item, Action) || Item <- Items],
 
925
    case reltool_server:set_apps(Xref, NewApps) of
 
926
        {ok, []} ->
 
927
            ok;
 
928
        {ok, Warnings} ->
 
929
            Msg = lists:flatten([[W, $\n] || W <- Warnings]),
 
930
            display_message(Msg, ?wxICON_WARNING);
 
931
        {error, Reason} ->
 
932
            display_message(Reason, ?wxICON_ERROR)
 
933
    end,
 
934
    [ok = reltool_app_win:refresh(AW#app_win.pid) || AW <- AppWins],
 
935
    redraw_apps(S).
 
936
 
 
937
do_set_sys(#state{sys = Sys, xref_pid = Xref, status_bar = Bar} = S) ->
 
938
    wxStatusBar:setStatusText(Bar, "Processing libraries..."),
 
939
    Status = reltool_server:set_sys(Xref, Sys),
 
940
    check_and_refresh(S, Status).
 
941
 
 
942
move_app(S, {_ItemNo, AppBase}, Action) ->
 
943
    {AppName, _Vsn} = reltool_utils:split_app_name(AppBase), 
 
944
    {ok, OldApp} = reltool_server:get_app(S#state.xref_pid, AppName),
 
945
    AppCond = 
 
946
        case Action of
 
947
            whitelist_add ->
 
948
                case OldApp#app.incl_cond of
 
949
                    include   -> undefined;
 
950
                    exclude   -> include;
 
951
                    undefined -> include
 
952
                end;
 
953
            whitelist_del ->
 
954
                undefined;
 
955
            blacklist_add -> 
 
956
                exclude;
 
957
            blacklist_del ->
 
958
                undefined;
 
959
            _ ->
 
960
                error_logger:format("~p~p got unexpected app button event: ~p ~p\n",
 
961
                                    [?MODULE, self(), Action, AppBase]),
 
962
                OldApp#app.incl_cond
 
963
        end,
 
964
    OldApp#app{incl_cond = AppCond}.
 
965
 
 
966
do_set_app(#state{xref_pid = Xref, app_wins = AppWins} = S, NewApp) ->
 
967
    {ok, AnalysedApp, Warnings} = reltool_server:set_app(Xref, NewApp),
 
968
    [ok = reltool_app_win:refresh(AW#app_win.pid) || AW <- AppWins],
 
969
    S2 = redraw_apps(S),
 
970
    case Warnings of
 
971
        [] ->
 
972
            ignore;
 
973
        _ ->
 
974
            Msg = lists:flatten([[W, $\n] || W <- Warnings]),
 
975
            display_message(Msg, ?wxICON_WARNING)
 
976
    end,
 
977
    {ok, AnalysedApp, S2}.
 
978
 
 
979
redraw_apps(#state{xref_pid = Xref,
 
980
                   source = SourceCtrl,
 
981
                   whitelist = WhiteCtrl,
 
982
                   blacklist = BlackCtrl,
 
983
                   derived = DerivedCtrl} = S) ->
 
984
    {ok, SourceApps} = reltool_server:get_apps(Xref, source),
 
985
    {ok, WhiteApps} = reltool_server:get_apps(Xref, whitelist),
 
986
    {ok, BlackApps} = reltool_server:get_apps(Xref, blacklist),
 
987
    {ok, DerivedApps} = reltool_server:get_apps(Xref, derived),
 
988
 
 
989
    BadApps = fun(#app{used_by_apps = UsedBy} = A) when UsedBy =/= [] ->
 
990
                      A#app{status = missing};
 
991
                 (A) ->
 
992
                      A
 
993
              end,
 
994
    BlackApps2 = lists:map(BadApps, BlackApps),
 
995
    redraw_apps(SourceApps, SourceCtrl, ?CROSS_IMAGE, ?WARN_IMAGE),
 
996
    WhiteN = redraw_apps(WhiteApps, WhiteCtrl, ?TICK_IMAGE, ?ERR_IMAGE),
 
997
    redraw_apps(BlackApps2, BlackCtrl, ?CROSS_IMAGE, ?WARN_IMAGE),
 
998
    DerivedN = redraw_apps(DerivedApps, DerivedCtrl, ?TICK_IMAGE, ?ERR_IMAGE),
 
999
    Status = lists:concat([WhiteN, " whitelisted modules and ",
 
1000
                           DerivedN, " derived modules."]),
 
1001
    wxStatusBar:setStatusText(S#state.status_bar, Status),
 
1002
    S.
 
1003
 
 
1004
redraw_apps(Apps, ListCtrl, OkImage, ErrImage) ->
 
1005
    do_redraw_apps(ListCtrl, Apps, OkImage, ErrImage).
 
1006
 
 
1007
do_redraw_apps(ListCtrl, [], _OkImage, _ErrImage) ->
 
1008
    wxListCtrl:deleteAllItems(ListCtrl),
 
1009
    0;
 
1010
do_redraw_apps(ListCtrl, Apps, OkImage, ErrImage) ->
 
1011
    OldItems = reltool_utils:get_items(ListCtrl),
 
1012
    wxListCtrl:deleteAllItems(ListCtrl),
 
1013
    AddImage =
 
1014
        fun(App) ->
 
1015
                case App#app.status of
 
1016
                    ok -> {OkImage, App#app.label, App};
 
1017
                    missing -> {ErrImage, App#app.label, App}
 
1018
                end
 
1019
        end,
 
1020
    ImageApps = lists:map(AddImage, Apps),
 
1021
    Show =
 
1022
        fun({ImageId, Text, App}, {Row, ModCount, Items}) ->
 
1023
                wxListCtrl:insertItem(ListCtrl, Row, ""), 
 
1024
                if (Row rem 2) =:= 0 -> 
 
1025
                        wxListCtrl:setItemBackgroundColour(ListCtrl, Row, {240,240,255});
 
1026
                   true ->
 
1027
                        ignore
 
1028
                end,
 
1029
                wxListCtrl:setItem(ListCtrl, Row, ?APPS_APP_COL, Text, [{imageId, ImageId}]),
 
1030
                N = length([M || M <- App#app.mods, M#mod.is_included =:= true]),
 
1031
                {Row + 1, ModCount + N, [{Row, Text} | Items]}
 
1032
        end,
 
1033
    {_, N, NewItems} = wx:foldl(Show, {0, 0, []}, lists:sort(ImageApps)),
 
1034
    reltool_utils:select_items(ListCtrl, OldItems, lists:reverse(NewItems)),
 
1035
    N.
 
1036
 
 
1037
update_app_graph(S) ->
 
1038
    {ok, WhiteApps} = reltool_server:get_apps(S#state.xref_pid, whitelist),
 
1039
    {ok, DerivedApps} = reltool_server:get_apps(S#state.xref_pid, derived),
 
1040
 
 
1041
    WhiteNames = [A#app.name || A <- WhiteApps],
 
1042
    DerivedNames = [A#app.name || A <- DerivedApps],
 
1043
    Nodes = WhiteNames ++ DerivedNames,
 
1044
    %% WhiteUses = [N || A <- WhiteApps, N <- A#app.uses_apps, lists:member(N, Nodes)],
 
1045
    %% DerivedUses = [N || A <- DerivedApps, N <- A#app.uses_apps, lists:member(N, Nodes)],
 
1046
 
 
1047
    WhiteLinks = [[A#app.name, U] || A <- WhiteApps,
 
1048
                                     U <- A#app.uses_apps,
 
1049
                                     U =/= A#app.name,
 
1050
                                     lists:member(U, Nodes)],
 
1051
    DerivedLinks = [[A#app.name, U] || A <- DerivedApps,
 
1052
                                       U <- A#app.uses_apps,
 
1053
                                       U =/= A#app.name,
 
1054
                                       lists:member(U, Nodes)],    
 
1055
    Links = lists:usort(WhiteLinks ++ DerivedLinks),
 
1056
    %% io:format("Links: ~p\n", [Links]),
 
1057
    Title = lists:concat([?APPLICATION, " - application graph"]),
 
1058
    create_fgraph_window(S, Title, Nodes, Links).
 
1059
 
 
1060
update_mod_graph(S) ->
 
1061
    {ok, WhiteApps} = reltool_server:get_apps(S#state.xref_pid, whitelist),
 
1062
    {ok, DerivedApps} = reltool_server:get_apps(S#state.xref_pid, derived),
 
1063
    WhiteMods = lists:usort([M || A <- WhiteApps, M <- A#app.mods, M#mod.is_included =:= true]),
 
1064
    DerivedMods = lists:usort([M || A <- DerivedApps, M <- A#app.mods, M#mod.is_included =:= true]),
 
1065
 
 
1066
    WhiteNames = [M#mod.name || M <- WhiteMods],
 
1067
    DerivedNames = [M#mod.name || M <- DerivedMods],
 
1068
    Nodes = WhiteNames ++ DerivedNames,
 
1069
 
 
1070
    WhiteLinks = [[M#mod.name, U] || M <- WhiteMods,
 
1071
                                     U <- M#mod.uses_mods,
 
1072
                                     U =/= M#mod.name,
 
1073
                                     lists:member(U, Nodes)],
 
1074
    DerivedLinks = [[M#mod.name, U] || M <- DerivedMods,
 
1075
                                       U <- M#mod.uses_mods,
 
1076
                                       U =/= M#mod.name,
 
1077
                                       lists:member(U, Nodes)],
 
1078
    Links = lists:usort(WhiteLinks ++ DerivedLinks),
 
1079
    %% io:format("Links: ~p\n", [Links]),
 
1080
    Title = lists:concat([?APPLICATION, " - module graph"]),
 
1081
    create_fgraph_window(S, Title, Nodes, Links).
 
1082
 
 
1083
create_fgraph_window(S, Title, Nodes, Links) ->
 
1084
    Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title, []),
 
1085
    wxFrame:setSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
 
1086
    Panel = wxPanel:new(Frame, []),
 
1087
    Options = [{size, {lists:max([100, ?WIN_WIDTH - 100]), ?WIN_HEIGHT}}],
 
1088
    {Server, Fgraph} = reltool_fgraph_win:new(Panel, Options),
 
1089
    Choose = fun(?MISSING_APP) -> alternate;
 
1090
                (_) -> default
 
1091
             end,
 
1092
    [reltool_fgraph_win:add_node(Server, N, Choose(N)) || N <- Nodes],
 
1093
    [reltool_fgraph_win:add_link(Server, {From, To}) || [From, To] <- Links],
 
1094
 
 
1095
    Sizer = wxBoxSizer:new(?wxVERTICAL),
 
1096
    wxSizer:add(Sizer, Fgraph, [{flag, ?wxEXPAND}, {proportion, 1}]),
 
1097
    wxPanel:setSizer(Panel, Sizer),
 
1098
    %% wxSizer:fit(Sizer, Frame),
 
1099
    %% wxSizer:setSizeHints(Sizer, Frame),
 
1100
    wxFrame:connect(Frame, close_window),
 
1101
    wxFrame:show(Frame),
 
1102
    FW = #fgraph_win{frame = Frame, pid = Server},
 
1103
    S#state{fgraph_wins = [FW | S#state.fgraph_wins]}.
 
1104
 
 
1105
reset_config(#state{status_bar = Bar} = S) ->
 
1106
    wxStatusBar:setStatusText(Bar, "Processing libraries..."),
 
1107
    Status = reltool_server:reset_config(S#state.xref_pid),
 
1108
    check_and_refresh(S, Status).
 
1109
 
 
1110
undo_config(#state{status_bar = Bar} = S) ->
 
1111
    wxStatusBar:setStatusText(Bar, "Processing libraries..."),
 
1112
    ok = reltool_server:undo_config(S#state.xref_pid),
 
1113
    refresh(S).
 
1114
 
 
1115
load_config(#state{status_bar = Bar, config_file = OldFile} = S) ->
 
1116
    Style = ?wxFD_OPEN bor ?wxFD_FILE_MUST_EXIST,
 
1117
    case select_file(S#state.frame, "Load configuration from file", OldFile, Style) of
 
1118
        {ok, NewFile} ->
 
1119
            wxStatusBar:setStatusText(Bar, "Processing libraries..."),
 
1120
            Status = reltool_server:load_config(S#state.xref_pid, NewFile),
 
1121
            check_and_refresh(S#state{config_file = NewFile}, Status);
 
1122
        cancel ->
 
1123
            S
 
1124
    end.
 
1125
 
 
1126
save_config(#state{config_file = OldFile} = S) ->
 
1127
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT, 
 
1128
    case select_file(S#state.frame, "Save configuration to file", OldFile, Style) of
 
1129
        {ok, NewFile} ->
 
1130
            Status = reltool_server:save_config(S#state.xref_pid, NewFile),
 
1131
            check_and_refresh(S#state{config_file = NewFile}, Status);
 
1132
        cancel ->
 
1133
            S
 
1134
    end.
 
1135
 
 
1136
gen_rel_files(#state{target_dir = OldDir} = S) ->
 
1137
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT, 
 
1138
    OldDir = filename:join([OldDir, "my_rel_file" ++ ".rel"]),
 
1139
    case select_dir(S#state.frame, "Generate rel, script and boot files on directory", OldDir, Style) of
 
1140
        {ok, NewDir} ->
 
1141
            Status = reltool_server:gen_rel_files(S#state.xref_pid, NewDir),
 
1142
            check_and_refresh(S, Status);
 
1143
        cancel ->
 
1144
            S
 
1145
    end.
 
1146
 
 
1147
gen_target(#state{target_dir = OldDir} = S) ->
 
1148
    Style = ?wxFD_SAVE bor ?wxFD_OVERWRITE_PROMPT, 
 
1149
    case select_dir(S#state.frame, "Generate target system to directory", OldDir, Style) of
 
1150
        {ok, NewDir} ->
 
1151
            Status = reltool_server:gen_target(S#state.xref_pid, NewDir),
 
1152
            check_and_refresh(S#state{target_dir = NewDir}, Status);
 
1153
        cancel ->
 
1154
            S
 
1155
    end.
 
1156
 
 
1157
select_file(Frame, Message, DefaultFile, Style) ->
 
1158
    Dialog = wxFileDialog:new(Frame,
 
1159
                              [{message, Message},
 
1160
                               {defaultDir, filename:dirname(DefaultFile)},
 
1161
                               {defaultFile, filename:basename(DefaultFile)},
 
1162
                               {style, Style}]),
 
1163
    Choice = 
 
1164
        case wxMessageDialog:showModal(Dialog) of
 
1165
            ?wxID_CANCEL ->  cancel;
 
1166
            ?wxID_OK -> {ok, wxFileDialog:getPath(Dialog)}
 
1167
        end,
 
1168
    wxFileDialog:destroy(Dialog),
 
1169
    Choice.
 
1170
 
 
1171
select_dir(Frame, Message, DefaultDir, Style) ->
 
1172
    Dialog = wxDirDialog:new(Frame,
 
1173
                             [{title, Message},
 
1174
                              {defaultPath, DefaultDir},
 
1175
                              {style, Style}]),
 
1176
    Choice = 
 
1177
        case wxMessageDialog:showModal(Dialog) of
 
1178
            ?wxID_CANCEL ->  cancel;
 
1179
            ?wxID_OK -> {ok, wxDirDialog:getPath(Dialog)}
 
1180
        end,
 
1181
    wxDirDialog:destroy(Dialog),
 
1182
    Choice.
 
1183
 
 
1184
check_and_refresh(S, Status) ->
 
1185
    case Status of
 
1186
        ok ->
 
1187
            true;
 
1188
        {ok, []} ->
 
1189
            true;
 
1190
        {ok, Warnings} ->
 
1191
            Q = lists:flatten([[W, $\n] || W <- Warnings]),
 
1192
            undo_dialog(S, "Do you want to perform the update despite these warnings?\n\n" ++ Q);
 
1193
        {error, Reason} when is_list(Reason) ->
 
1194
            display_message(Reason, ?wxICON_ERROR),
 
1195
            false;
 
1196
        {error, Reason} ->
 
1197
            Msg = lists:flatten(io_lib:format("Error:\n\n~p\n", [Reason])),
 
1198
            display_message(Msg, ?wxICON_ERROR),
 
1199
            false
 
1200
    end,
 
1201
    refresh(S).
 
1202
 
 
1203
refresh(S) ->
 
1204
    {ok, Sys} = reltool_server:get_sys(S#state.xref_pid),
 
1205
    [ok = reltool_app_win:refresh(AW#app_win.pid) || AW <- S#state.app_wins],
 
1206
    S2 = S#state{sys = Sys},
 
1207
    S3 = redraw_libs(S2),
 
1208
    redraw_apps(S3).
 
1209
    
 
1210
undo_dialog(S, Question) ->
 
1211
    Dialog = wxMessageDialog:new(wx:null(),
 
1212
                                 Question,
 
1213
                                 [{style, ?wxYES_NO bor ?wxICON_ERROR}]),
 
1214
    Answer = wxMessageDialog:showModal(Dialog),
 
1215
    wxMessageDialog:destroy(Dialog),
 
1216
    case Answer of
 
1217
        ?wxID_YES ->
 
1218
            true;
 
1219
        ?wxID_NO  ->
 
1220
            reltool_server:undo_config(S#state.xref_pid),
 
1221
            false
 
1222
    end.
 
1223
 
 
1224
display_message(Message, Icon) ->
 
1225
    Dialog = wxMessageDialog:new(wx:null(),
 
1226
                                 Message,
 
1227
                                 [{style, ?wxOK bor Icon}]),
 
1228
    wxMessageDialog:showModal(Dialog),
 
1229
    wxMessageDialog:destroy(Dialog).
 
1230
 
 
1231
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1232
%% sys callbacks
 
1233
 
 
1234
system_continue(_Parent, _Debug, S) ->
 
1235
    ?MODULE:loop(S).
 
1236
 
 
1237
system_terminate(Reason, _Parent, _Debug, _S) ->
 
1238
    exit(Reason).
 
1239
 
 
1240
system_code_change(S,_Module,_OldVsn,_Extra) ->
 
1241
    {ok, S}.