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

« back to all changes in this revision

Viewing changes to lib/reltool/src/reltool_mod_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-2011. 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_mod_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
         xref_pid,
40
40
         rel_pid,
73
73
-define(WIN_HEIGHT, 600).
74
74
 
75
75
-define(CLOSE_ITEM, ?wxID_EXIT).    %% Use OS specific version if available
76
 
-define(ABOUT_ITEM, ?wxID_ABOUT).   %% Use OS specific 
 
76
-define(ABOUT_ITEM, ?wxID_ABOUT).   %% Use OS specific
77
77
-define(CONTENTS_ITEM, 300).
78
78
-define(SEARCH_ENTRY,   413).
79
79
-define(GOTO_ENTRY,     414).
87
87
%% Client
88
88
 
89
89
start_link(WxEnv, Xref, RelPid, Common, ModName) ->
90
 
    proc_lib:start_link(?MODULE, init, [self(), WxEnv, Xref, RelPid, Common, ModName], infinity, []).
 
90
    proc_lib:start_link(?MODULE,
 
91
                        init,
 
92
                        [self(), WxEnv, Xref, RelPid, Common, ModName],
 
93
                        infinity,
 
94
                        []).
91
95
 
92
96
raise(Pid) ->
93
97
    reltool_utils:cast(Pid, raise).
127
131
    receive
128
132
        Msg ->
129
133
            %% io:format("~s~p -> ~p\n", [S#state.name, self(), Msg]),
130
 
            case Msg of     
 
134
            case Msg of
131
135
                {system, From, SysMsg} ->
132
136
                    Dbg = C#common.sys_debug,
133
 
                    sys:handle_system_msg(SysMsg, From, S#state.parent_pid, ?MODULE, Dbg, S);
 
137
                    sys:handle_system_msg(SysMsg,
 
138
                                          From,
 
139
                                          S#state.parent_pid,
 
140
                                          ?MODULE,
 
141
                                          Dbg,
 
142
                                          S);
134
143
                {cast, _From, raise} ->
135
144
                    wxFrame:raise(S#state.frame),
136
145
                    wxFrame:setFocus(S#state.frame),
169
178
 
170
179
create_window(#state{mod = Mod, name = ModStr} = S) ->
171
180
    Title = atom_to_list(?APPLICATION) ++ " - " ++
172
 
        atom_to_list(Mod#mod.app_name) ++ " - " ++ 
 
181
        atom_to_list(Mod#mod.app_name) ++ " - " ++
173
182
        ModStr ++ ".erl",
174
183
    Frame = wxFrame:new(wx:null(), ?wxID_ANY, Title, []),
175
184
    %% wxFrame:setSize(Frame, {?WIN_WIDTH, ?WIN_HEIGHT}),
177
186
    StatusBar = wxFrame:createStatusBar(Frame,[]),
178
187
 
179
188
    Book = wxNotebook:new(Panel, ?wxID_ANY, []),
180
 
    
 
189
 
181
190
    S2 = S#state{frame = Frame,
182
191
                 panel = Panel,
183
192
                 book = Book,
204
213
    Panel = wxPanel:new(S#state.book, []),
205
214
    Main = wxBoxSizer:new(?wxHORIZONTAL),
206
215
 
207
 
    UsedByCtrl = create_mods_list_ctrl(Panel, Main, "Modules used by others", " and their applications"),
 
216
    UsedByCtrl = create_mods_list_ctrl(Panel,
 
217
                                       Main,
 
218
                                       "Modules used by others",
 
219
                                       " and their applications"),
208
220
    wxSizer:add(Main,
209
221
                wxStaticLine:new(Panel, [{style, ?wxLI_VERTICAL}]),
210
222
                [{border, 2}, {flag, ?wxALL bor ?wxEXPAND}]),
211
 
    UsesCtrl = create_mods_list_ctrl(Panel, Main, "Used modules",  " and their applications"),
 
223
    UsesCtrl = create_mods_list_ctrl(Panel,
 
224
                                     Main,
 
225
                                     "Used modules",
 
226
                                     " and their applications"),
212
227
    S2 = S#state{deps_used_by_ctrl = UsedByCtrl,
213
228
                 deps_uses_ctrl = UsesCtrl},
214
229
    redraw_mods(S2),
242
257
    %% wxListCtrl:setColumnWidth(ListCtrl, ?MODS_APP_COL, ?MODS_APP_COL_WIDTH),
243
258
    wxListItem:destroy(ListItem),
244
259
 
245
 
    wxEvtHandler:connect(ListCtrl, size, [{skip, true}, {userData, mods_list_ctrl}]),
246
 
    wxListCtrl:connect(ListCtrl, command_list_item_activated, [{userData, open_app}]),
 
260
    wxEvtHandler:connect(ListCtrl, size,
 
261
                         [{skip, true}, {userData, mods_list_ctrl}]),
 
262
    wxListCtrl:connect(ListCtrl, command_list_item_activated,
 
263
                       [{userData, open_app}]),
247
264
    wxWindow:connect(ListCtrl, enter_window),
248
265
 
249
266
    wxSizer:add(Sizer, ListCtrl,
252
269
                 {proportion, 1}]),
253
270
    ListCtrl.
254
271
 
255
 
create_code_page(#state{book = Book, code_pages = Pages, name = ModStr} = S, PageName) ->
 
272
create_code_page(#state{book = Book, code_pages = Pages, name = ModStr} = S,
 
273
                 PageName) ->
256
274
    case find_page(S, PageName) of
257
275
        not_found ->
258
276
            Page = do_create_code_page(S, PageName),
260
278
            Pos = length(Pages2),
261
279
            wxNotebook:setSelection(Book, Pos),
262
280
            case find_page(S, ?INITIAL_CODE_PAGE_NAME) of
263
 
                not_found -> 
 
281
                not_found ->
264
282
                    ignore;
265
283
                {found, _, CodePos} ->
266
284
                    %% Rename initial code page
288
306
do_create_code_page(#state{xref_pid = Xref, mod = M} = S, PageName) ->
289
307
    Panel = wxPanel:new(S#state.book, []),
290
308
    Editor = create_editor(Panel),
291
 
    ToolTip = "Double click on a function call to search the function definition.",
 
309
    ToolTip = "Double click on a function call to "
 
310
        "search the function definition.",
292
311
    wxBitmapButton:setToolTip(Editor, ToolTip),
293
312
    {Objs, Data, SearchSz} = create_search_area(Panel),
294
313
 
295
314
    {ok, App} = reltool_server:get_app(Xref, M#mod.app_name),
296
 
    ErlBin = 
 
315
    ErlBin =
297
316
        case App#app.is_escript of
298
317
            true -> find_escript_bin(App, M);
299
318
            false -> find_regular_bin(App, M)
300
319
        end,
301
 
    
 
320
 
302
321
    load_code(Editor, ErlBin),
303
 
    
 
322
 
304
323
    Sizer = wxBoxSizer:new(?wxVERTICAL),
305
324
    wxSizer:add(Sizer, Editor, [{flag, ?wxEXPAND}, {proportion, 1}]),
306
325
    wxSizer:add(Sizer, SearchSz, [{flag, ?wxEXPAND}]),
307
326
    wxPanel:setSizer(Panel, Sizer),
308
327
    wxNotebook:addPage(S#state.book, Panel, PageName, []),
309
 
    #code_page{name  = PageName, editor = Editor, find_objs = Objs, find_data = Data}.
 
328
    #code_page{name  = PageName,
 
329
               editor = Editor,
 
330
               find_objs = Objs,
 
331
               find_data = Data}.
310
332
 
311
333
find_regular_bin(App, Mod) ->
312
334
    ActiveDir = App#app.active_dir,
313
335
    SrcDir = filename:join([ActiveDir, "src"]),
314
336
    ModStr = atom_to_list(Mod#mod.name),
315
 
    Base = ModStr ++ ".erl",
316
 
    Find = fun(F, _Acc) -> file:read_file(F) end,
317
 
    case filelib:fold_files(SrcDir, Base, true, Find, {error, enoent}) of
 
337
    Base = "^" ++ ModStr ++ "\\.erl$",
 
338
    Find = fun(F, _Acc) -> throw(file:read_file(F)) end,
 
339
    case catch filelib:fold_files(SrcDir, Base, true, Find, {error, enoent}) of
318
340
        {ok, Bin} ->
319
341
            Bin;
320
342
        {error, enoent} ->
322
344
            BeamFile = filename:join([ActiveDir, "ebin", ModStr ++ ".beam"]),
323
345
            case beam_lib:chunks(BeamFile, [abstract_code]) of
324
346
                {ok,{_,[{abstract_code,{_,AC}}]}} ->
325
 
                    list_to_binary(erl_prettypr:format(erl_syntax:form_list(AC)));
 
347
                    IoList = erl_prettypr:format(erl_syntax:form_list(AC)),
 
348
                    list_to_binary(IoList);
326
349
                _ ->
327
 
                    list_to_binary(["%% Bad luck, cannot find any debug info in the file \"", BeamFile])
 
350
                    list_to_binary(["%% Bad luck, cannot find any "
 
351
                                    "debug info in the file \"", BeamFile])
328
352
            end
329
353
    end.
330
354
 
340
364
                             [_] ->
341
365
                                 Bin = GetBin(),
342
366
                                 case beam_lib:version(Bin) of
343
 
                                     {ok,{M, _}} when M =:= ModName; FullName =:= "." ->
344
 
                                         case beam_lib:chunks(Bin, [abstract_code]) of
 
367
                                     {ok,{M, _}} when M =:= ModName;
 
368
                                                      FullName =:= "." ->
 
369
                                         case beam_lib:chunks(Bin,
 
370
                                                              [abstract_code]) of
345
371
                                             {ok,{_,[{abstract_code,{_,AC}}]}} ->
346
 
                                                 {obj, list_to_binary(erl_prettypr:format(erl_syntax:form_list(AC)))};
 
372
                                                 Form =
 
373
                                                     erl_syntax:form_list(AC),
 
374
                                                 IoList =
 
375
                                                     erl_prettypr:format(Form),
 
376
                                                 {obj,
 
377
                                                  list_to_binary(IoList)};
347
378
                                             _ ->
348
379
                                                 Acc
349
380
                                         end;
363
394
                {fun(FullName, _GetInfo, GetBin, Acc) ->
364
395
                         io:format("", []),
365
396
                         case filename:split(FullName) of
366
 
                             [_AppName, "ebin", F] when F =:= ObjFile, Acc =:= NotFound ->
367
 
                                 case beam_lib:chunks(GetBin(), [abstract_code]) of
 
397
                             [_AppName, "ebin", F]
 
398
                               when F =:= ObjFile, Acc =:= NotFound ->
 
399
                                 case beam_lib:chunks(GetBin(),
 
400
                                                      [abstract_code]) of
368
401
                                     {ok,{_,[{abstract_code,{_,AC}}]}} ->
369
 
                                         {obj, list_to_binary(erl_prettypr:format(erl_syntax:form_list(AC)))};
 
402
                                         Form = erl_syntax:form_list(AC),
 
403
                                         IoList = erl_prettypr:format(Form),
 
404
                                         {obj, list_to_binary(IoList)};
370
405
                                     _ ->
371
406
                                         Acc
372
407
                                 end;
379
414
                 filename:dirname(ActiveDir)}
380
415
        end,
381
416
    try
382
 
        case escript:foldl(Fun, NotFound, Escript) of
 
417
        case reltool_utils:escript_foldl(Fun, NotFound, Escript) of
383
418
            {ok, {text, Bin}} ->
384
419
                Bin;
385
420
            {ok, {obj, Bin}} ->
386
421
                Bin;
387
422
            _ ->
388
 
                list_to_binary(["%% Bad luck, cannot find the code in the escript ", Escript, "."])
 
423
                list_to_binary(["%% Bad luck, cannot find the "
 
424
                                "code in the escript ", Escript, "."])
389
425
        end
390
 
    catch 
 
426
    catch
391
427
        throw:Reason when is_list(Reason) ->
392
 
            list_to_binary(["%% Bad luck, cannot find the code in the escript ", Escript, ": ", Reason])
 
428
            list_to_binary(["%% Bad luck, cannot find the code "
 
429
                            "in the escript ", Escript, ": ", Reason])
393
430
    end.
394
431
 
395
432
create_config_page(S) ->
400
437
handle_event(#state{xref_pid = Xref} = S, Wx) ->
401
438
    %% io:format("wx: ~p\n", [Wx]),
402
439
    case Wx of
403
 
        #wx{obj= ListCtrl, userData = mods_list_ctrl, event = #wxSize{type = size, size = {W, _H}}} ->
 
440
        #wx{obj= ListCtrl,
 
441
            userData = mods_list_ctrl,
 
442
            event = #wxSize{type = size, size = {W, _H}}} ->
404
443
            wxListCtrl:setColumnWidth(ListCtrl, ?MODS_MOD_COL, (2 * W) div 3),
405
444
            wxListCtrl:setColumnWidth(ListCtrl, ?MODS_APP_COL, W div 3),
406
445
            S;
407
446
        #wx{userData = open_app,
408
447
            obj = ListCtrl,
409
 
            event = #wxList{type = command_list_item_activated, itemIndex = Pos}} ->
 
448
            event = #wxList{type = command_list_item_activated,
 
449
                            itemIndex = Pos}} ->
410
450
            ModStr = wxListCtrl:getItemText(ListCtrl, Pos),
411
451
            ModName = list_to_atom(ModStr),
412
452
            {ok, Mod} = reltool_server:get_mod(Xref, ModName),
431
471
                    Page = lists:nth(N, S#state.code_pages),
432
472
                    S#state{active_page = Page}
433
473
            end;
434
 
        #wx{event = #wxCommand{type = command_button_clicked}, userData = history_back} ->
 
474
        #wx{event = #wxCommand{type = command_button_clicked},
 
475
            userData = history_back} ->
435
476
            goto_back(S);
436
477
        #wx{obj = ObjRef, event = #wxMouse{type = enter_window}} ->
437
478
            wxWindow:setFocus(ObjRef),
438
479
            S;
439
480
        _ ->
440
 
            error_logger:format("~p~p got unexpected mod event from wx:\n\t~p\n",
 
481
            error_logger:format("~p~p got unexpected mod event from "
 
482
                                "wx:\n\t~p\n",
441
483
                                [?MODULE, self(), Wx]),
442
484
            S
443
485
    end.
450
492
                              uses_mods = UsesModNames,
451
493
                              used_by_mods = UsedByModNames},
452
494
                   status_bar = Bar}) ->
453
 
    InclStatus = 
 
495
    InclStatus =
454
496
        case IsIncl of
455
497
            true when IsPre =:= true -> "Whitelist - ";
456
498
            true -> "Derived - ";
458
500
            undefined -> "Source - "
459
501
        end,
460
502
    Status = lists:concat([InclStatus,
461
 
                           " uses ", length(UsesModNames), " modules and ",
462
 
                           " is used by ", length(UsedByModNames), " modules."]),
 
503
                           " uses ", length(UsesModNames),
 
504
                           " modules and ",
 
505
                           " is used by ", length(UsedByModNames),
 
506
                           " modules."]),
463
507
    wxStatusBar:setStatusText(Bar, Status),
464
508
    UsesMods = [select_image(Xref, M) || M <- UsesModNames],
465
509
    UsedByMods = [select_image(Xref, M) || M <- UsedByModNames],
470
514
    {ok, M} = reltool_server:get_mod(Xref, ModName),
471
515
    Image =
472
516
        case M#mod.is_included of
473
 
            _ when M#mod.app_name =:= ?MISSING_APP -> ?ERR_IMAGE;
 
517
            _ when M#mod.app_name =:= ?MISSING_APP_NAME -> ?ERR_IMAGE;
474
518
            true -> ?TICK_IMAGE;
475
519
            false -> ?WARN_IMAGE;
476
520
            undefined -> ?ERR_IMAGE
483
527
    wxListCtrl:deleteAllItems(ListCtrl),
484
528
    Add =
485
529
        fun({ImageId, AppName, #mod{name = ModName}}, Row) ->
486
 
                wxListCtrl:insertItem(ListCtrl, Row, ""), 
487
 
                if (Row rem 2) =:= 0 -> 
488
 
                        wxListCtrl:setItemBackgroundColour(ListCtrl, Row, {240,240,255});
 
530
                wxListCtrl:insertItem(ListCtrl, Row, ""),
 
531
                if (Row rem 2) =:= 0 ->
 
532
                        wxListCtrl:setItemBackgroundColour(ListCtrl,
 
533
                                                           Row,
 
534
                                                           {240,240,255});
489
535
                   true ->
490
536
                        ignore
491
537
                end,
515
561
    wxStyledTextCtrl:setSelection(Editor, Left, Right),
516
562
    S;
517
563
goto_line(#state{active_page = P} =S, Str) when is_list(Str) ->
518
 
    try 
 
564
    try
519
565
        LineNo = list_to_integer(Str),
520
566
        CurrentPos = wxStyledTextCtrl:getCurrentPos(P#code_page.editor),
521
567
        S2 = add_pos_to_history(S, CurrentPos),
522
568
        goto_line(S2, LineNo - 1)
523
 
    catch 
 
569
    catch
524
570
        _:_ ->
525
571
            wxStatusBar:setStatusText(S#state.status_bar, "Not a line number"),
526
572
            S
527
 
    end.    
 
573
    end.
528
574
 
529
575
find_string(S, Str) ->
530
576
    find_string(S, Str, 0).
535
581
    wxTextCtrl:setValue(TextCtrl, Str),
536
582
    S2.
537
583
 
538
 
find_string(#state{active_page = #code_page{editor = Editor,
539
 
                                            find_objs = #find_objs{radio={NextO,_,CaseO}},
540
 
                                            find_data = #find_data{found = Found} = Data} = P} = S,
 
584
find_string(#state{active_page =
 
585
                   #code_page{editor = Editor,
 
586
                              find_objs = #find_objs{radio={NextO,_,CaseO}},
 
587
                              find_data = #find_data{found = Found} = Data} = P} = S,
541
588
            Str,
542
589
            Flag) ->
543
590
    wxStyledTextCtrl:hideSelection(Editor, true),
544
591
    Dir  = wxRadioButton:getValue(NextO) xor wx_misc:getKeyState(?WXK_SHIFT),
545
592
    Case = wxCheckBox:getValue(CaseO),
546
593
    Pos =
547
 
        if 
 
594
        if
548
595
            Found, Dir ->  %% Forward Continuation
549
596
                wxStyledTextCtrl:getAnchor(Editor);
550
 
            Found ->  %% Backward Continuation 
 
597
            Found ->  %% Backward Continuation
551
598
                wxStyledTextCtrl:getCurrentPos(Editor);
552
599
            Dir ->   %% Forward wrap
553
600
                0;
556
603
        end,
557
604
    wxStyledTextCtrl:gotoPos(Editor,Pos),
558
605
    wxStyledTextCtrl:searchAnchor(Editor),
559
 
    Flag2 = 
 
606
    Flag2 =
560
607
        if  Case -> Flag bor ?wxSTC_FIND_MATCHCASE;
561
608
            true -> Flag
562
609
        end,
563
 
    Res = 
564
 
        if 
 
610
    Res =
 
611
        if
565
612
            Dir -> wxStyledTextCtrl:searchNext(Editor, Flag2, Str);
566
613
            true -> wxStyledTextCtrl:searchPrev(Editor, Flag2, Str)
567
614
        end,
568
 
    Found2 = 
 
615
    Found2 =
569
616
        case Res >= 0 of        
570
 
            true -> 
 
617
            true ->
571
618
                wxStyledTextCtrl:hideSelection(Editor, false),
572
619
                %% io:format("Found ~p ~n",[Res]),
573
620
                LineNo = wxStyledTextCtrl:lineFromPosition(Editor,Res),
576
623
                true;
577
624
            false ->
578
625
                wxStatusBar:setStatusText(S#state.status_bar,
579
 
                                          "Not found (Hit Enter to wrap search)"),
 
626
                                          "Not found (Hit Enter to "
 
627
                                          "wrap search)"),
580
628
                false
581
 
        end, 
 
629
        end,
582
630
    P2 = P#code_page{find_data = Data#find_data{found = Found2}},
583
 
    Pages = lists:keystore(P#code_page.name, #code_page.name, S#state.code_pages, P2),
 
631
    Pages = lists:keystore(P#code_page.name,
 
632
                           #code_page.name,
 
633
                           S#state.code_pages,
 
634
                           P2),
584
635
    S#state{active_page = P2, code_pages = Pages}.
585
636
 
586
637
goto_function(S, Editor) ->
589
640
    Left = wxStyledTextCtrl:wordStartPosition(Editor, CurrentPos, true),
590
641
    Right = wxStyledTextCtrl:wordEndPosition(Editor, CurrentPos, true),
591
642
    ColonPos = Left - 1,
592
 
    Left2 = 
 
643
    Left2 =
593
644
        case wxStyledTextCtrl:getCharAt(Editor, ColonPos) of
594
645
            $: ->
595
646
                wxStyledTextCtrl:wordStartPosition(Editor, ColonPos, true);
596
647
            _ ->
597
648
                Left
598
649
        end,
599
 
    Right2 = 
 
650
    Right2 =
600
651
        case wxStyledTextCtrl:getCharAt(Editor, Right) of
601
652
            $: ->
602
653
                wxStyledTextCtrl:wordEndPosition(Editor, Right + 1, true);
623
674
    find_regexp_forward(S, "^" ++ FunName ++ "(");
624
675
do_goto_function(S, [ModStr, FunStr]) ->
625
676
    case reltool_server:get_mod(S#state.xref_pid, list_to_atom(ModStr)) of
626
 
        {ok, Mod} when Mod#mod.app_name =/= ?MISSING_APP ->
 
677
        {ok, Mod} when Mod#mod.app_name =/= ?MISSING_APP_NAME ->
627
678
            S2 = create_code_page(S#state{mod = Mod}, ModStr),
628
679
            find_regexp_forward(S2, "^" ++ FunStr ++ "(");
629
680
        {ok, _} ->
630
 
            wxStatusBar:setStatusText(S#state.status_bar, "No such module: " ++ ModStr),
 
681
            wxStatusBar:setStatusText(S#state.status_bar,
 
682
                                      "No such module: " ++ ModStr),
631
683
            S
632
684
    end.
633
685
 
634
 
goto_back(#state{active_page = #code_page{editor = Editor, find_data = Data} = Page,
 
686
goto_back(#state{active_page =
 
687
                 #code_page{editor = Editor, find_data = Data} = Page,
635
688
                 code_pages = Pages} = S) ->
636
689
    case Data#find_data.history of
637
690
        [PrevPos | History] ->
638
691
            LineNo = wxStyledTextCtrl:lineFromPosition(Editor, PrevPos),
639
692
            Data2 = Data#find_data{history = History},
640
693
            Page2 = Page#code_page{find_data = Data2},
641
 
            Pages2 = lists:keystore(Page2#code_page.name, #code_page.name, Pages, Page2),
642
 
            goto_line(S#state{active_page = Page2, code_pages = Pages2}, LineNo);
 
694
            Pages2 = lists:keystore(Page2#code_page.name,
 
695
                                    #code_page.name,
 
696
                                    Pages,
 
697
                                    Page2),
 
698
            goto_line(S#state{active_page = Page2, code_pages = Pages2},
 
699
                      LineNo);
643
700
        [] ->
644
701
            wxStatusBar:setStatusText(S#state.status_bar, "No history"),
645
702
            S
646
703
    end.
647
704
 
648
 
add_pos_to_history(#state{active_page = Page, code_pages = Pages} = S, CurrentPos) ->
 
705
add_pos_to_history(#state{active_page = Page, code_pages = Pages} = S,
 
706
                   CurrentPos) ->
649
707
    Data = Page#code_page.find_data,
650
708
    Data2 = Data#find_data{history = [CurrentPos | Data#find_data.history]},
651
709
    Page2 = Page#code_page{find_data = Data2},
652
 
    Pages2 = lists:keystore(Page2#code_page.name, #code_page.name, Pages, Page2),
 
710
    Pages2 =
 
711
        lists:keystore(Page2#code_page.name, #code_page.name, Pages, Page2),
653
712
    S#state{active_page = Page2, code_pages = Pages2}.
654
713
 
655
714
create_editor(Parent) ->
685
744
                       wxStyledTextCtrl:styleSetFont(Ed, Style, FixedFont),
686
745
                       wxStyledTextCtrl:styleSetForeground(Ed, Style, Color)
687
746
               end,
688
 
    [SetStyle(Style) || Style <- Styles],
 
747
    lists:foreach(fun (Style) -> SetStyle(Style) end, Styles),
689
748
    wxStyledTextCtrl:setKeyWords(Ed, 0, keyWords()),
690
749
 
691
750
    %% Margins Markers
692
751
    %% Breakpoint Should be a pixmap?
693
 
    wxStyledTextCtrl:markerDefine(Ed, 0, ?wxSTC_MARK_CIRCLE, [{foreground, {170,20,20}}]),    
694
 
    wxStyledTextCtrl:markerDefine(Ed, 0, ?wxSTC_MARK_CIRCLE, [{background, {200,120,120}}]),    
695
 
    %% Disabled Breakpoint 
696
 
    wxStyledTextCtrl:markerDefine(Ed, 1, ?wxSTC_MARK_CIRCLE, [{foreground, {20,20,170}}]),
697
 
    wxStyledTextCtrl:markerDefine(Ed, 1, ?wxSTC_MARK_CIRCLE, [{background, {120,120,200}}]),
698
 
    
 
752
    wxStyledTextCtrl:markerDefine(Ed, 0, ?wxSTC_MARK_CIRCLE,
 
753
                                  [{foreground, {170,20,20}}]),
 
754
    wxStyledTextCtrl:markerDefine(Ed, 0, ?wxSTC_MARK_CIRCLE,
 
755
                                  [{background, {200,120,120}}]),
 
756
    %% Disabled Breakpoint
 
757
    wxStyledTextCtrl:markerDefine(Ed, 1, ?wxSTC_MARK_CIRCLE,
 
758
                                  [{foreground, {20,20,170}}]),
 
759
    wxStyledTextCtrl:markerDefine(Ed, 1, ?wxSTC_MARK_CIRCLE,
 
760
                                  [{background, {120,120,200}}]),
 
761
 
699
762
    %% Current Line
700
 
    wxStyledTextCtrl:markerDefine(Ed, 2, ?wxSTC_MARK_ARROW,  [{foreground, {20,170,20}}]),
701
 
    wxStyledTextCtrl:markerDefine(Ed, 2, ?wxSTC_MARK_ARROW,  [{background, {200,255,200}}]),
702
 
    wxStyledTextCtrl:markerDefine(Ed, 3, ?wxSTC_MARK_BACKGROUND, [{background, {200,255,200}}]),
 
763
    wxStyledTextCtrl:markerDefine(Ed, 2, ?wxSTC_MARK_ARROW,
 
764
                                  [{foreground, {20,170,20}}]),
 
765
    wxStyledTextCtrl:markerDefine(Ed, 2, ?wxSTC_MARK_ARROW,
 
766
                                  [{background, {200,255,200}}]),
 
767
    wxStyledTextCtrl:markerDefine(Ed, 3, ?wxSTC_MARK_BACKGROUND,
 
768
                                  [{background, {200,255,200}}]),
703
769
 
704
770
    %% Scrolling
705
 
    Policy = ?wxSTC_CARET_SLOP bor ?wxSTC_CARET_JUMPS bor ?wxSTC_CARET_EVEN, 
 
771
    Policy = ?wxSTC_CARET_SLOP bor ?wxSTC_CARET_JUMPS bor ?wxSTC_CARET_EVEN,
706
772
    wxStyledTextCtrl:setYCaretPolicy(Ed, Policy, 3),
707
773
    wxStyledTextCtrl:setVisiblePolicy(Ed, Policy, 3),
708
774
 
714
780
 
715
781
create_search_area(Parent) ->
716
782
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
717
 
    wxSizer:add(Sizer, wxStaticText:new(Parent, ?wxID_ANY, "Find:"), 
 
783
    wxSizer:add(Sizer, wxStaticText:new(Parent, ?wxID_ANY, "Find:"),
718
784
                [{flag,?wxALIGN_CENTER_VERTICAL}]),
719
 
    TC1 = wxTextCtrl:new(Parent, ?SEARCH_ENTRY, [{style, ?wxTE_PROCESS_ENTER}]), 
 
785
    TC1 = wxTextCtrl:new(Parent, ?SEARCH_ENTRY, [{style, ?wxTE_PROCESS_ENTER}]),
720
786
    wxSizer:add(Sizer, TC1,  [{proportion,3}, {flag, ?wxEXPAND}]),
721
787
    Nbtn = wxRadioButton:new(Parent, ?wxID_ANY, "Next"),
722
788
    wxRadioButton:setValue(Nbtn, true),
726
792
    Cbtn = wxCheckBox:new(Parent, ?wxID_ANY, "Match Case"),
727
793
    wxSizer:add(Sizer,Cbtn,[{flag,?wxALIGN_CENTER_VERTICAL}]),
728
794
    wxSizer:add(Sizer, 15,15, [{proportion,1}, {flag, ?wxEXPAND}]),
729
 
    wxSizer:add(Sizer, wxStaticText:new(Parent, ?wxID_ANY, "Goto Line:"), 
 
795
    wxSizer:add(Sizer, wxStaticText:new(Parent, ?wxID_ANY, "Goto Line:"),
730
796
                [{flag,?wxALIGN_CENTER_VERTICAL}]),
731
 
    TC2 = wxTextCtrl:new(Parent, ?GOTO_ENTRY, [{style, ?wxTE_PROCESS_ENTER}]), 
 
797
    TC2 = wxTextCtrl:new(Parent, ?GOTO_ENTRY, [{style, ?wxTE_PROCESS_ENTER}]),
732
798
    wxSizer:add(Sizer, TC2,  [{proportion,0}, {flag, ?wxEXPAND}]),
733
799
    Button = wxButton:new(Parent, ?wxID_ANY, [{label, "Back"}]),
734
800
    wxSizer:add(Sizer, Button, []),
735
801
 
736
 
    wxEvtHandler:connect(Button, command_button_clicked, [{userData, history_back}]),
 
802
    wxEvtHandler:connect(Button, command_button_clicked,
 
803
                         [{userData, history_back}]),
737
804
    %% wxTextCtrl:connect(TC1, command_text_updated),
738
805
    wxTextCtrl:connect(TC1, command_text_enter),
739
806
    %% wxTextCtrl:connect(TC1, kill_focus),
748
815
    wxStyledTextCtrl:setTextRaw(Ed, <<Code/binary, 0:8>>),
749
816
    Lines = wxStyledTextCtrl:getLineCount(Ed),
750
817
    Sz = trunc(math:log10(Lines))+1,
751
 
    LW = wxStyledTextCtrl:textWidth(Ed, ?wxSTC_STYLE_LINENUMBER, lists:duplicate(Sz, $9)),
 
818
    LW = wxStyledTextCtrl:textWidth(Ed,
 
819
                                    ?wxSTC_STYLE_LINENUMBER,
 
820
                                    lists:duplicate(Sz, $9)),
752
821
    %%io:format("~p ~p ~p~n", [Lines, Sz, LW]),
753
822
    wxStyledTextCtrl:setMarginWidth(Ed, 0, LW+5),
754
823
    wxStyledTextCtrl:setReadOnly(Ed, true),