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

« back to all changes in this revision

Viewing changes to lib/debugger/src/dbg_ui_trace_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 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-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(dbg_ui_trace_win).
106
106
                   gs:read('CodeArea', height) +
107
107
                   gs:read('RB1', height) +
108
108
                   gs:read('ButtonArea', height) +
109
 
                   max(gs:read('EvalArea', height),
 
109
                   erlang:max(gs:read('EvalArea', height),
110
110
                       gs:read('BindArea', height)) +
111
111
                   gs:read('RB2', height) +
112
112
                   gs:read('TraceArea', height)}),
147
147
    H = gs:read(Win, height),
148
148
 
149
149
    H2 = if
150
 
             Bu1==close, Bu2==open ->
 
150
             Bu1 =:= close, Bu2 =:= open ->
151
151
                 resize_button_area(open, width, W-4),
152
152
                 gs:config('ButtonArea', {height, 30}),
153
153
                 H+30;
154
 
             Bu1==open, Bu2==close ->
 
154
             Bu1 =:= open, Bu2 =:= close ->
155
155
                 gs:config('ButtonArea', [{width, 0}, {height, 0}]),
156
156
                 H-30;
157
157
             true -> H
158
158
         end,
159
159
    H3 = if
160
 
             Ev1==close, Ev2==open, Bi1==open ->
 
160
             Ev1 =:= close, Ev2 =:= open, Bi1 =:= open ->
161
161
                 Wnew1 = round((W-10-4)/2), % W = window/2 - rb - pads
162
162
                 Hbi1 = gs:read('BindArea', height), % H = bind area h
163
163
                 resize_eval_area(open, width, Wnew1),
167
167
                 resize_bind_area(open, width,
168
168
                                  Wnew1-gs:read('BindArea', width)),
169
169
                 H2;
170
 
             Ev1==close, Ev2==open, Bi1==close ->
 
170
             Ev1 =:= close, Ev2 =:= open, Bi1 =:= close ->
171
171
                 resize_eval_area(open, width, W-4),
172
172
                 resize_eval_area(open, height, 200),
173
173
                 H2+200;
174
 
             Ev1==open, Ev2==close, Bi1==open ->
 
174
             Ev1 =:= open, Ev2 =:= close, Bi1 =:= open ->
175
175
                 gs:config('EvalArea', [{width,0}, {height,0}]),
176
176
                 gs:config('RB3', [{width, 0}, {height, 0}]),
177
177
                 Wnew2 = W-4,
178
178
                 resize_bind_area(open, width,
179
179
                                  Wnew2-gs:read('BindArea', width)),
180
180
                 H2;
181
 
             Ev1==open, Ev2==close, Bi1==close ->
 
181
             Ev1 =:= open, Ev2 =:= close, Bi1 =:= close ->
182
182
                 Hs1 = gs:read('EvalArea', height),
183
183
                 gs:config('EvalArea', [{width, 0}, {height, 0}]),
184
184
                 H2-Hs1;
185
185
             true -> H2
186
186
         end,
187
187
    H4 = if
188
 
             Bi1==close, Bi2==open, Ev2==open ->
 
188
             Bi1 =:= close, Bi2 =:= open, Ev2 =:= open ->
189
189
                 Wnew3 = round((W-10-4)/2), % W = window/2 - rb - pads
190
190
                 Hs2 = gs:read('EvalArea', height), % H = eval area h
191
191
                 resize_bind_area(open, width, Wnew3),
194
194
                 resize_eval_area(open, width,
195
195
                                  Wnew3-gs:read('EvalArea', width)),
196
196
                 H3;
197
 
             Bi1==close, Bi2==open, Ev2==close ->
 
197
             Bi1 =:= close, Bi2 =:= open, Ev2 =:= close ->
198
198
                 resize_bind_area(open, width, W-4),
199
199
                 resize_bind_area(open, height, 200),
200
200
                 H3+200;
201
 
             Bi1==open, Bi2==close, Ev2==open ->
 
201
             Bi1 =:= open, Bi2 =:= close, Ev2 =:= open ->
202
202
                 gs:config('BindArea', [{width, 0}, {height, 0}]),
203
203
                 gs:config('RB3', [{width, 0}, {height, 0}]),
204
204
                 Wnew4 = W-4,
205
205
                 resize_eval_area(open, width,
206
206
                                  Wnew4-gs:read('EvalArea', width)),
207
207
                 H3;
208
 
             Bi1==open, Bi2==close, Ev2==close ->
 
208
             Bi1 =:= open, Bi2 =:= close, Ev2 =:= close ->
209
209
                 Hbi2 = gs:read('BindArea', height),
210
210
                 gs:config('BindArea', [{width, 0}, {height, 0}]),
211
211
                 H3-Hbi2;
212
212
             true -> H3
213
213
         end,
214
214
    H5 = if
215
 
             Tr1==close, Tr2==open ->
 
215
             Tr1 =:= close, Tr2 =:= open ->
216
216
                 resize_trace_area(open, width, W-4),
217
217
                 resize_trace_area(open, height, 200),
218
218
                 H4+200;
219
 
             Tr1==open, Tr2==close ->
 
219
             Tr1 =:= open, Tr2 =:= close ->
220
220
                 Hf = gs:read('TraceArea', height),
221
221
                 gs:config('TraceArea', [{width, 0}, {height, 0}]),
222
222
                 H4-Hf;
226
226
 
227
227
    RB1old = rb1(OldFlags), RB1new = rb1(NewFlags),
228
228
    if
229
 
        RB1old==close, RB1new==open ->
 
229
        RB1old =:= close, RB1new =:= open ->
230
230
            gs:config('RB1', [{width, W-4}, {height, 10}]),
231
231
            gs:config(Win, {height, gs:read(Win, height)+10});
232
 
        RB1old==open, RB1new==close ->
 
232
        RB1old =:= open, RB1new =:= close ->
233
233
            gs:config('RB1', [{width, 0}, {height, 0}, lower]),
234
234
            gs:config(Win, {height, gs:read(Win, height)-10});
235
235
        true -> ignore
237
237
 
238
238
    RB2old = rb2(OldFlags), RB2new = rb2(NewFlags),
239
239
    if
240
 
        RB2old==close, RB2new==open ->
 
240
        RB2old =:= close, RB2new =:= open ->
241
241
            gs:config('RB2', [{width, W-4}, {height, 10}]),
242
242
            gs:config(Win, {height,gs:read(Win, height)+10});
243
 
        RB2old==open, RB2new==close ->          
 
243
        RB2old =:= open, RB2new =:= close ->
244
244
            gs:config('RB2', [{width, 0}, {height, 0}, lower]),
245
245
            gs:config(Win, {height, gs:read(Win, height)-10});
246
246
        true -> ignore
301
301
%%     Cond = null | {Mod, Func}
302
302
%%--------------------------------------------------------------------
303
303
add_break(WinInfo, Menu, {{Mod,Line},[Status|_Options]}=Break) ->
304
 
    case lists:keysearch(Mod, 1, WinInfo#winInfo.editors) of
305
 
        {value, {Mod, Editor}} ->
 
304
    case lists:keyfind(Mod, 1, WinInfo#winInfo.editors) of
 
305
        {Mod, Editor} ->
306
306
            add_break_to_code(Editor, Line, Status);
307
307
        false -> ignore
308
308
    end,
309
309
    add_break_to_menu(WinInfo, Menu, Break).
310
310
 
311
311
add_break_to_code(Editor, Line, Status) ->
312
 
    Color = if Status==active -> red; Status==inactive -> blue end,
 
312
    Color = if Status =:= active -> red; Status =:= inactive -> blue end,
313
313
    config_editor(Editor, [{overwrite,{{Line,0},"-@-  "}},
314
314
                           {fg,{{{Line,0},{Line,lineend}}, Color}}]).
315
315
 
330
330
%%     Cond = null | {Mod, Func}
331
331
%%--------------------------------------------------------------------
332
332
update_break(WinInfo, {{Mod,Line},[Status|_Options]}=Break) ->
333
 
    case lists:keysearch(Mod, 1, WinInfo#winInfo.editors) of
334
 
        {value, {Mod, Editor}} ->
 
333
    case lists:keyfind(Mod, 1, WinInfo#winInfo.editors) of
 
334
        {Mod, Editor} ->
335
335
            add_break_to_code(Editor, Line, Status);
336
336
        false -> ignore
337
337
    end,
352
352
%%   Point = {Mod, Line}
353
353
%%--------------------------------------------------------------------
354
354
delete_break(WinInfo, {Mod,Line}=Point) ->
355
 
    case lists:keysearch(Mod, 1, WinInfo#winInfo.editors) of
356
 
        {value, {Mod, Editor}} -> delete_break_from_code(Editor, Line);
 
355
    case lists:keyfind(Mod, 1, WinInfo#winInfo.editors) of
 
356
        {Mod, Editor} -> delete_break_from_code(Editor, Line);
357
357
        false -> ignore
358
358
    end,
359
359
    delete_break_from_menu(WinInfo, Point).
379
379
    clear_breaks(WinInfo, all).
380
380
clear_breaks(WinInfo, Mod) ->
381
381
    Remove = if
382
 
                 Mod==all -> WinInfo#winInfo.breaks;
 
382
                 Mod =:= all -> WinInfo#winInfo.breaks;
383
383
                 true ->
384
384
                     lists:filter(fun(#breakInfo{point={Mod2,_L}}) ->
385
385
                                          if
386
 
                                              Mod2==Mod -> true;
 
386
                                              Mod2 =:= Mod -> true;
387
387
                                              true -> false
388
388
                                          end
389
389
                                  end,
450
450
%% Note: remove_code/2 should not be used for currently shown module.
451
451
%%--------------------------------------------------------------------
452
452
is_shown(WinInfo, Mod) ->
453
 
    case lists:keysearch(Mod, 1, WinInfo#winInfo.editors) of
454
 
        {value, {Mod, Editor}} ->
 
453
    case lists:keyfind(Mod, 1, WinInfo#winInfo.editors) of
 
454
        {Mod, Editor} ->
455
455
            gs:config(Editor, raise),
456
456
            {true, WinInfo#winInfo{editor={Mod, Editor}}};
457
457
        false -> false
459
459
 
460
460
show_code(WinInfo, Mod, Contents) ->
461
461
    Editors = WinInfo#winInfo.editors,
462
 
    {Flag, Editor} = case lists:keysearch(Mod, 1, Editors) of
463
 
                         {value, {Mod, Ed}} -> {existing, Ed};
 
462
    {Flag, Editor} = case lists:keyfind(Mod, 1, Editors) of
 
463
                         {Mod, Ed} -> {existing, Ed};
464
464
                         false -> {new, code_editor()}
465
465
                     end,
466
 
 
467
466
    %% Insert code and update breakpoints, if any
468
467
    config_editor(Editor, [raise, clear]),
469
468
    show_code(Editor, Contents),
470
469
    lists:foreach(fun(BreakInfo) ->
471
470
                          case BreakInfo#breakInfo.point of
472
 
                              {Mod2, Line} when Mod2==Mod ->
 
471
                              {Mod2, Line} when Mod2 =:= Mod ->
473
472
                                  Status = BreakInfo#breakInfo.status,
474
473
                                  add_break_to_code(Editor, Line,Status);
475
474
                              _Point -> ignore
476
475
                          end
477
476
                  end,
478
477
                  WinInfo#winInfo.breaks),
479
 
 
480
478
    case Flag of
481
479
        existing ->
482
480
            WinInfo#winInfo{editor={Mod, Editor}};
485
483
                            editors=[{Mod, Editor} | Editors]}
486
484
    end.
487
485
        
488
 
show_code(Editor, Text) when length(Text)>1500 ->
 
486
show_code(Editor, Text) when length(Text) > 1500 ->
489
487
    %% Add some text at a time so that other processes may get scheduled
490
488
    Str = string:sub_string(Text, 1, 1500),
491
489
    config_editor(Editor, {insert,{'end', Str}}),
494
492
    config_editor(Editor, {insert,{'end',Text}}).
495
493
 
496
494
show_no_code(WinInfo) ->
497
 
    {value, {'$top', Editor}} =
498
 
        lists:keysearch('$top', 1, WinInfo#winInfo.editors),
 
495
    {'$top', Editor} = lists:keyfind('$top', 1, WinInfo#winInfo.editors),
499
496
    gs:config(Editor, raise),
500
497
    WinInfo#winInfo{editor={'$top', Editor}}.
501
498
 
502
499
remove_code(WinInfo, Mod) ->
503
500
    Editors = WinInfo#winInfo.editors,
504
 
    case lists:keysearch(Mod, 1, Editors) of
505
 
        {value, {Mod, Editor}} ->
 
501
    case lists:keyfind(Mod, 1, Editors) of
 
502
        {Mod, Editor} ->
506
503
            gs:destroy(Editor),
507
504
            WinInfo#winInfo{editors=lists:keydelete(Mod, 1, Editors)};
508
505
        false ->
509
506
            WinInfo
510
507
    end.
511
 
    
512
508
 
513
509
%%--------------------------------------------------------------------
514
510
%% mark_line(WinInfo, Line, How) -> WinInfo
522
518
    mark_line2(Editor, WinInfo#winInfo.marked_line, false),
523
519
    mark_line2(Editor, Line, How),
524
520
    if
525
 
        Line/=0 -> config_editor(Editor, {vscrollpos, Line-5});
 
521
        Line =/= 0 -> config_editor(Editor, {vscrollpos, Line-5});
526
522
        true -> ignore
527
523
    end,
528
524
    WinInfo#winInfo{marked_line=Line}.
537
533
                 false -> "   "
538
534
             end,
539
535
    Font = if
540
 
               How==false -> dbg_ui_win:font(normal);
 
536
               How =:= false -> dbg_ui_win:font(normal);
541
537
               true -> dbg_ui_win:font(bold)
542
538
           end,
543
539
    config_editor(Editor, [{overwrite, {{Line,5}, Prefix}},
558
554
    %% help window, it must be checked that it is correct
559
555
    Size = gs:read(Editor, size),
560
556
    if
561
 
        Line==0 ->
 
557
        Line =:= 0 ->
562
558
            select_line(Editor, WinInfo#winInfo.selected_line, false),
563
559
            WinInfo#winInfo{selected_line=0};
564
 
        Line<Size ->
 
560
        Line < Size ->
565
561
            select_line(Editor, Line, true),
566
562
            config_editor(Editor, {vscrollpos, Line-5}),
567
563
            WinInfo#winInfo{selected_line=Line};
712
708
        {Row, _} ->
713
709
            {Mod, _Editor} = WinInfo#winInfo.editor,
714
710
            Point = {Mod, Row},
715
 
            case lists:keysearch(Point, #breakInfo.point,
 
711
            case lists:keymember(Point, #breakInfo.point,
716
712
                                 WinInfo#winInfo.breaks) of
717
 
                {value, _BreakInfo} -> {break, Point, delete};
718
 
                false -> {break, Point, add}
 
713
                false -> {break, Point, add};
 
714
                true  -> {break, Point, delete}
719
715
            end;
720
716
        {Row2, _} ->
721
717
            select_line(Editor, Row2, true),
776
772
 
777
773
code_editor(Name, W, H) ->
778
774
    Editor = if
779
 
                 Name==null -> gs:editor('CodeArea', []);
 
775
                 Name =:= null -> gs:editor('CodeArea', []);
780
776
                 true -> gs:editor(Name, 'CodeArea', [])
781
777
             end,
782
778
    gs:config(Editor, [{x,5}, {y,30}, {width,W}, {height,H},
814
810
     {'Where','WhereButton'}, {'Up','UpButton'}, {'Down','DownButton'}].
815
811
 
816
812
is_button(Name) ->
817
 
    case lists:keysearch(Name, 1, buttons()) of
818
 
        {value, {Name, Button}} -> {true, Button};
 
813
    case lists:keyfind(Name, 1, buttons()) of
 
814
        {Name, Button} -> {true, Button};
819
815
        false -> false
820
816
    end.
821
817
 
847
843
 
848
844
eval_area({Ev,Bi}, X, Y, FrameOpts, Win) ->
849
845
    {W,H} = if
850
 
                Ev==open -> {289,200};
 
846
                Ev =:= open -> {289,200};
851
847
                true -> {0,0}
852
848
            end,
853
849
    Font = dbg_ui_win:font(normal),
870
866
               {font_style,{{{1,0},'end'},Font}}]),
871
867
    gs:config('EvalEditor', {enable, false}),
872
868
    if
873
 
        Ev==open, Bi==close -> resize_eval_area(Ev, width, 257);
 
869
        Ev =:= open, Bi =:= close -> resize_eval_area(Ev, width, 257);
874
870
        true -> ignore
875
871
    end.
876
872
 
891
887
 
892
888
bind_area({Ev,Bi}, X, Y, FrameOpts, Win) ->
893
889
    {W,H} = if
894
 
                Bi==open -> {249,200};
 
890
                Bi =:= open -> {249,200};
895
891
                true -> {0,0}
896
892
            end,
897
893
    gs:frame('BindArea', Win,
908
904
                 {text,{1,"Name"}}, {text,{2,"Value"}}, {font,Font}]),
909
905
    gs:config('BindGrid', {rows,{1,1}}),
910
906
    if
911
 
        Bi==open, Ev==close -> resize_bind_area(Bi, width, 297);
 
907
        Bi =:= open, Ev =:= close -> resize_bind_area(Bi, width, 297);
912
908
        true -> ignore
913
909
    end.
914
910
 
993
989
 
994
990
rb1({_Bu,Ev,Bi,Tr}) ->
995
991
    if
996
 
        Ev==close, Bi==close, Tr==close -> close;
 
992
        Ev =:= close, Bi =:= close, Tr =:= close -> close;
997
993
        true -> open
998
994
    end.
999
995
    
1000
996
rb2({_Bu,Ev,Bi,Tr}) ->
1001
997
    if
1002
 
        Tr==open ->
 
998
        Tr =:= open ->
1003
999
            if
1004
 
                Ev==close, Bi==close -> close;
 
1000
                Ev =:= close, Bi =:= close -> close;
1005
1001
                true -> open
1006
1002
            end;
1007
1003
        true -> close
1009
1005
    
1010
1006
rb3({_Bu,Ev,Bi,_Tr}) ->
1011
1007
    if
1012
 
        Ev==open, Bi==open -> open;
 
1008
        Ev =:= open, Bi =:= open -> open;
1013
1009
        true -> close
1014
1010
    end.
1015
1011
 
1032
1028
    gs:config('RB3', {y,Y3}),
1033
1029
    gs:config('BindArea', {y,Y3}),
1034
1030
    
1035
 
    Y4 = Y3 + max(gs:read('EvalArea', height),
 
1031
    Y4 = Y3 + erlang:max(gs:read('EvalArea', height),
1036
1032
                  gs:read('BindArea', height)),
1037
1033
    gs:config('RB2', {y,Y4}),
1038
1034
    
1061
1057
    OldH = 25+gs:read('CodeArea', height)+
1062
1058
        gs:read('RB1', height)+
1063
1059
        gs:read('ButtonArea', height)+
1064
 
        max(gs:read('EvalArea', height), gs:read('BindArea', height))+
 
1060
        erlang:max(gs:read('EvalArea', height), gs:read('BindArea', height))+
1065
1061
        gs:read('RB2', height)+
1066
1062
        gs:read('TraceArea', height),
1067
1063
 
1068
1064
    %% Adjust width unless it is unchanged or less than minimum width
1069
1065
    if
1070
 
        OldW/=NewW ->
 
1066
        OldW =/= NewW ->
1071
1067
            {Dcode,Deval,Dbind} = configure_widths(OldW,NewW,Flags),
1072
1068
            resize_code_area(WinInfo, width, Dcode),
1073
1069
            case rb1(Flags) of
1090
1086
    
1091
1087
    %% Adjust height unless it is unchanged or less than minimum height
1092
1088
    if
1093
 
        OldH/=NewH ->
 
1089
        OldH =/= NewH ->
1094
1090
            {Dcode2,Deval2,Dtrace} = configure_heights(OldH,NewH,Flags),
1095
1091
            resize_code_area(WinInfo, height, Dcode2),
1096
1092
            resize_eval_area(Ev, height, Deval2),
1112
1108
    {_Bu,Ev,Bi,_Tr} = Flags,
1113
1109
 
1114
1110
    %% Difference between old and new width, considering min window width
1115
 
    Diff = abs(max(OldW,330)-max(NewW,330)),
 
1111
    Diff = abs(erlang:max(OldW,330)-erlang:max(NewW,330)),
1116
1112
    
1117
1113
    %% Check how much the frames can be resized in reality
1118
1114
    Limits = if
1119
1115
                 %% Window larger
1120
 
                 NewW>OldW ->
 
1116
                 NewW > OldW ->
1121
1117
                     if
1122
 
                         Ev==open,Bi==open -> {0,Diff,Diff};
1123
 
                         Ev==open -> {0,Diff,0};
1124
 
                         Bi==open -> {0,0,Diff};
 
1118
                         Ev =:= open, Bi =:= open -> {0,Diff,Diff};
 
1119
                         Ev =:= open -> {0,Diff,0};
 
1120
                         Bi =:= open -> {0,0,Diff};
1125
1121
                         true -> {Diff,0,0}
1126
1122
                     end;
1127
1123
                 
1129
1125
                 %% and current size
1130
1126
                 OldW>NewW ->
1131
1127
                     if
1132
 
                         Ev==open,Bi==open ->
 
1128
                         Ev =:= open, Bi =:= open ->
1133
1129
                             {0,
1134
1130
                              gs:read('EvalArea',width)-204,
1135
1131
                              gs:read('BindArea',width)-112};
1136
 
                         Ev==open -> {0,Diff,0};
1137
 
                         Bi==open -> {0,0,Diff};
 
1132
                         Ev =:= open -> {0,Diff,0};
 
1133
                         Bi =:= open -> {0,0,Diff};
1138
1134
                         true -> {Diff,0,0}
1139
1135
                     end
1140
1136
             end,
1142
1138
    case Limits of
1143
1139
 
1144
1140
        %% No Shell or Bind frame, larger window
1145
 
        {T,0,0} when NewW>OldW -> {T,0,0};
 
1141
        {T,0,0} when NewW > OldW -> {T,0,0};
1146
1142
        
1147
1143
        %% No Shell or Bind frame, smaller window
1148
 
        {T,0,0} when OldW>NewW -> {-T,0,0};
 
1144
        {T,0,0} when OldW > NewW -> {-T,0,0};
1149
1145
 
1150
1146
        %% Window larger; divide Diff among the frames and return result
1151
 
        {_,Sf,B} when NewW>OldW ->
 
1147
        {_,Sf,B} when NewW > OldW ->
1152
1148
            {_,Sf2,B2} = divide([{0,0},{0,Sf},{0,B}],Diff),
1153
1149
            {Sf2+B2,Sf2,B2};
1154
1150
 
1166
1162
 
1167
1163
    %% Difference between old and new height, considering min win height
1168
1164
    MinH = min_height(Flags),
1169
 
    Diff = abs(max(OldH,MinH)-max(NewH,MinH)),
 
1165
    Diff = abs(erlang:max(OldH,MinH)-erlang:max(NewH,MinH)),
1170
1166
    
1171
1167
    %% Check how much the frames can be resized in reality
1172
1168
    {T,Sf,Ff} = if
1173
1169
                  %% Window larger
1174
 
                  NewH>OldH ->
 
1170
                  NewH > OldH ->
1175
1171
                      {Diff,
1176
1172
                       if
1177
 
                           Ev==close, Bi==close -> 0;
 
1173
                           Ev =:= close, Bi =:= close -> 0;
1178
1174
                           true -> Diff
1179
1175
                       end,
1180
1176
                       if
1181
 
                           Tr==open -> Diff;
 
1177
                           Tr =:= open -> Diff;
1182
1178
                           true -> 0
1183
1179
                       end};
1184
1180
 
1185
1181
                  %% Window smaller; get difference between min size
1186
1182
                  %% and current size
1187
 
                  OldH>NewH ->
 
1183
                  OldH > NewH ->
1188
1184
                      {gs:read('CodeArea',height)-100,
1189
1185
                       if
1190
 
                           Ev==close, Bi==close -> 0;
 
1186
                           Ev =:= close, Bi =:= close -> 0;
1191
1187
                           true ->
1192
1188
                               if
1193
 
                                   Ev==open ->
 
1189
                                   Ev =:= open ->
1194
1190
                                       gs:read('EvalArea',height)-100;
1195
 
                                   Bi==open ->
 
1191
                                   Bi =:= open ->
1196
1192
                                       gs:read('BindArea',height)-100
1197
1193
                               end
1198
1194
                       end,
1199
1195
                       if
1200
 
                           Tr==open -> gs:read('TraceArea',height)-100;
 
1196
                           Tr =:= open -> gs:read('TraceArea',height)-100;
1201
1197
                           true -> 0
1202
1198
                       end}
1203
1199
              end,
1251
1247
 
1252
1248
    if
1253
1249
        %% All of Diff has been distributed
1254
 
        D==0 -> {T,S,F};
1255
 
        
 
1250
        D =:= 0 -> {T,S,F};
1256
1251
        true ->
1257
 
    
1258
1252
            %% For each element, try to add as much as possible of D
1259
1253
            {NewT,Dt} = divide2(D,T,Tmax),
1260
1254
            {NewS,Ds} = divide2(D,S,Smax),
1296
1290
               rblimits('RB2',W,H),
1297
1291
               rblimits('RB3',W,H)).
1298
1292
 
1299
 
resizeloop(WI, RB, Prev, {Min1,Max1},{Min2,Max2},{Min3,Max3}) ->
 
1293
resizeloop(WI, RB, Prev, {Min1,Max1}, {Min2,Max2}, {Min3,Max3}) ->
1300
1294
    receive
1301
 
        {gs,_,motion,_,[_,Y]} when RB=='RB1', Y>Min1,Y<Max1 ->
 
1295
        {gs,_,motion,_,[_,Y]} when RB =:= 'RB1', Y > Min1, Y < Max1 ->
1302
1296
            gs:config('RB1', {y,Y}),
1303
 
            resizeloop(WI, RB, Y, {Min1,Max1},{Min2,Max2},{Min3,Max3});
1304
 
        {gs,_,motion,_,_} when RB=='RB1' ->
1305
 
            resizeloop(WI, RB, Prev,{Min1,Max1},{Min2,Max2},{Min3,Max3});
 
1297
            resizeloop(WI, RB, Y, {Min1,Max1}, {Min2,Max2}, {Min3,Max3});
 
1298
        {gs,_,motion,_,_} when RB =:= 'RB1' ->
 
1299
            resizeloop(WI, RB, Prev, {Min1,Max1}, {Min2,Max2}, {Min3,Max3});
1306
1300
        
1307
 
        {gs,_,motion,_,[_,Y]} when RB=='RB2', Y>Min2,Y<Max2 ->
 
1301
        {gs,_,motion,_,[_,Y]} when RB =:= 'RB2', Y > Min2, Y < Max2 ->
1308
1302
            gs:config('RB2', {y,Y}),
1309
 
            resizeloop(WI, RB, Y, {Min1,Max1},{Min2,Max2},{Min3,Max3});
1310
 
        {gs,_,motion,_,_} when RB=='RB2' ->
1311
 
            resizeloop(WI, RB, Prev,{Min1,Max1},{Min2,Max2},{Min3,Max3});
 
1303
            resizeloop(WI, RB, Y, {Min1,Max1}, {Min2,Max2}, {Min3,Max3});
 
1304
        {gs,_,motion,_,_} when RB =:= 'RB2' ->
 
1305
            resizeloop(WI, RB, Prev, {Min1,Max1}, {Min2,Max2}, {Min3,Max3});
1312
1306
         
1313
 
        {gs,_,motion,_,[X,_]} when RB=='RB3', X>Min3,X<Max3 ->
 
1307
        {gs,_,motion,_,[X,_]} when RB =:= 'RB3', X > Min3, X < Max3 ->
1314
1308
            gs:config('RB3', {x,X}),
1315
 
            resizeloop(WI, RB, X, {Min1,Max1},{Min2,Max2},{Min3,Max3});
1316
 
        {gs,_,motion,_,_} when RB=='RB3' ->
1317
 
            resizeloop(WI, RB, Prev,{Min1,Max1},{Min2,Max2},{Min3,Max3});
 
1309
            resizeloop(WI, RB, X, {Min1,Max1}, {Min2,Max2}, {Min3,Max3});
 
1310
        {gs,_,motion,_,_} when RB =:= 'RB3' ->
 
1311
            resizeloop(WI, RB, Prev, {Min1,Max1}, {Min2,Max2}, {Min3,Max3});
1318
1312
        
1319
1313
        {gs,_,buttonrelease,_,_} ->
1320
1314
            resize_win(WI, RB, Prev)
1329
1323
    %% Resize Code, Evaluator and Binding areas
1330
1324
    resize_code_area(WinInfo, height, -Diff),
1331
1325
    if
1332
 
        S==close, Bi==close, F==open ->
 
1326
        S =:= close, Bi =:= close, F =:= open ->
1333
1327
            resize_trace_area(open, height, Diff);
1334
1328
        true ->
1335
1329
            resize_eval_area(S, height, Diff),
1388
1382
    RB2 = gs:read('RB2',height),
1389
1383
    FF = gs:read('TraceArea',height),
1390
1384
    Max = case RB2 of
1391
 
              0 when FF/=0 ->
 
1385
              0 when FF =/= 0 ->
1392
1386
                  H-112;
1393
1387
              _ ->
1394
1388
                  Y = gs:read('RB2',y),
1395
 
                  max(Min,Y-140)
 
1389
                  erlang:max(Min,Y-140)
1396
1390
          end,
1397
1391
    
1398
1392
    {Min,Max};
1399
1393
rblimits('RB2',_W,H) ->
1400
 
 
1401
 
    %% TraceFrame should not have height <100
 
1394
    %% TraceFrame should not have height < 100
1402
1395
    Max = H-112,
1403
 
    
1404
1396
    %% Min is decided by a minimum distance to 'RB1'
1405
1397
    Y = gs:read('RB1',y),
1406
 
    Min = min(Max,Y+140),
1407
 
    
 
1398
    Min = erlang:min(Max,Y+140),
1408
1399
    {Min,Max};
1409
1400
 
1410
1401
rblimits('RB3',W,_H) ->
1411
 
    
1412
1402
    %% Neither CodeArea nor BindArea should occupy 
1413
1403
    %% less than 1/3 of the total window width and EvalFrame should
1414
1404
    %% be at least 289 pixels wide
1415
 
    {max(round(W/3),289),round(2*W/3)}.
1416
 
 
1417
 
max(A, B) when A>B -> A;
1418
 
max(_A, B) -> B.
1419
 
 
1420
 
min(A, B) when A<B -> A;
1421
 
min(_A, B) -> B.
 
1405
    {erlang:max(round(W/3),289),round(2*W/3)}.
1422
1406
 
1423
1407
 
1424
1408
%%====================================================================
1490
1474
    end,
1491
1475
    Data;
1492
1476
helpwin_action(search, case_sensitive, _AttPid, _Ed, {Pos, CS}, _Win) ->
1493
 
    Bool = if CS==true -> false; CS==false -> true end,
 
1477
    Bool = if CS =:= true -> false; CS =:= false -> true end,
1494
1478
    {Pos, Bool};
1495
1479
helpwin_action(search, default, _AttPid, Editor, {Pos, CS}, Win) ->
1496
1480
    gs:config(lbl(Win), {label, {text, ""}}),
1523
1507
 
1524
1508
lowercase(true, Str) -> Str;
1525
1509
lowercase(false, Str) ->
1526
 
    lists:map(fun(Char) ->
1527
 
                      if
1528
 
                          Char>=$A, Char=<$Z -> Char+32;
1529
 
                          true -> Char
1530
 
                      end
1531
 
              end,
1532
 
              Str).
 
1510
    [if Char >= $A, Char =< $Z -> Char+32;
 
1511
        true -> Char
 
1512
     end || Char <- Str].
1533
1513
 
1534
1514
mark_string(Editor, {Row, Col}, Str) ->
1535
1515
    Between = {{Row,Col}, {Row,Col+length(Str)}},
1546
1526
                       {fg, {Between, black}}]).
1547
1527
 
1548
1528
helpwin(Type, GS, {X, Y}) ->
1549
 
    W = 200, Pad=10, Wbtn = 50,
 
1529
    W = 200, Pad = 10, Wbtn = 50,
1550
1530
 
1551
 
    Title =
1552
 
        case Type of search -> "Search"; gotoline -> "Go To Line" end,
 
1531
    Title = case Type of search -> "Search"; gotoline -> "Go To Line" end,
1553
1532
    Win = gs:window(GS, [{title, Title}, {x, X}, {y, Y}, {width, W},
1554
1533
                         {destroy, true}]),
1555
1534