Skip to content

Commit

Permalink
Fix "OK" spelling in debugger messages and variables
Browse files Browse the repository at this point in the history
Simple code refactor in the debugger: renames all the occurrences of
"Ok" to "OK" in the code, variable names and strings. This improves the
consistency of the code and follows the GTK UI where "OK" is always
used.
  • Loading branch information
jimenezrick authored and proxyles committed Nov 9, 2011
1 parent d90ccb6 commit 84d0304
Show file tree
Hide file tree
Showing 8 changed files with 37 additions and 37 deletions.
26 changes: 13 additions & 13 deletions lib/debugger/src/dbg_ui_break_win.erl
Original file line number Diff line number Diff line change
Expand Up @@ -81,12 +81,12 @@ create_win(GS, {X, Y}, function, Mod, _Line) ->
{pack_x, 2}, {pack_y, 3},
{selectmode, multiple}]),

%% Add Ok and Cancel buttons
{Wbtn, Hbtn} = dbg_ui_win:min_size(["Ok","Cancel"], 70, 30),
%% Add OK and Cancel buttons
{Wbtn, Hbtn} = dbg_ui_win:min_size(["OK","Cancel"], 70, 30),
Bot = gs:frame(Frm, [{pack_x, {1, 3}}, {pack_y, 4}]),
Ok = gs:button(Bot, [{x, Pad}, {y, Pad},
OK = gs:button(Bot, [{x, Pad}, {y, Pad},
{width, Wbtn}, {height, Hbtn},
{label, {text,"Ok"}}, {font, Font}]),
{label, {text,"OK"}}, {font, Font}]),
Cancel = gs:button(Bot, [{x, W-Pad-Wbtn}, {y, Pad},
{width, Wbtn}, {height, Hbtn},
{label, {text,"Cancel"}}, {font, Font}]),
Expand All @@ -95,7 +95,7 @@ create_win(GS, {X, Y}, function, Mod, _Line) ->
gs:config(Win, [{width, Wfrm}, {height, Hfrm}, {map, true}]),
#winInfo{type=function, win=Win,
packer=Frm, entries=Entries, trigger=enable,
ok=Ok, cancel=Cancel, listbox=Lb, funcs=[]};
ok=OK, cancel=Cancel, listbox=Lb, funcs=[]};
create_win(GS, {X, Y}, Type, Mod, Line) ->
Pad = 8,
W = 230,
Expand Down Expand Up @@ -161,12 +161,12 @@ create_win(GS, {X, Y}, Type, Mod, Line) ->
{align, w}, {group, Grp},
{data, {trigger, delete}}]),

%% Add Ok and Cancel buttons
{Wbtn, Hbtn} = dbg_ui_win:min_size(["Ok","Cancel"], 70, 30),
%% Add OK and Cancel buttons
{Wbtn, Hbtn} = dbg_ui_win:min_size(["OK","Cancel"], 70, 30),
Ybtn = Yacc + Pad + Hfrm + Pad,
Ok = gs:button(Win, [{x, Pad}, {y, Ybtn},
OK = gs:button(Win, [{x, Pad}, {y, Ybtn},
{width, Wbtn}, {height, Hbtn},
{label, {text,"Ok"}}, {font, Font}]),
{label, {text,"OK"}}, {font, Font}]),
gs:button(Win, [{x, W-Pad-Wbtn}, {y, Ybtn},
{width, Wbtn}, {height, Hbtn},
{label, {text,"Cancel"}}, {font, Font}]),
Expand All @@ -175,7 +175,7 @@ create_win(GS, {X, Y}, Type, Mod, Line) ->
gs:config(Win, [{width, W}, {height, Hwin}, {map, true}]),

#winInfo{type=Type, win=Win,
entries=Entries, trigger=enable, ok=Ok}.
entries=Entries, trigger=enable, ok=OK}.

%%--------------------------------------------------------------------
%% update_functions(WinInfo, Funcs) -> WinInfo
Expand Down Expand Up @@ -229,7 +229,7 @@ handle_event({gs, LB, keypress, window, [Key|_]}, WinInfo) ->
Key/='Tab', Key/='Return' ->
ignore;
true ->
handle_event({gs, LB, click, listbox, ["Ok"]}, WinInfo)
handle_event({gs, LB, click, listbox, ["OK"]}, WinInfo)
end;
handle_event({gs, Ent, keypress, Data, [Key|_]}, WinInfo) ->
case WinInfo#winInfo.type of
Expand All @@ -249,14 +249,14 @@ handle_event({gs, Ent, keypress, Data, [Key|_]}, WinInfo) ->
case next_entry(Ent, WinInfo#winInfo.entries) of
last ->
gs:config(WinInfo#winInfo.ok, flash),
handle_event({gs, Ent, click, Data, ["Ok"]}, WinInfo);
handle_event({gs, Ent, click, Data, ["OK"]}, WinInfo);
Next ->
gs:config(Next, {setfocus, true}),
ignore
end;
_Type -> ignore
end;
handle_event({gs, _Id, click, _Data, ["Ok"|_]}, WinInfo) ->
handle_event({gs, _Id, click, _Data, ["OK"|_]}, WinInfo) ->
case check_input(WinInfo#winInfo.entries) of
error -> ignore;
Data when WinInfo#winInfo.type/=function ->
Expand Down
8 changes: 4 additions & 4 deletions lib/debugger/src/dbg_ui_edit_win.erl
Original file line number Diff line number Diff line change
Expand Up @@ -64,13 +64,13 @@ create_win(GS, {X, Y}, Title, Prompt, {Type, Value}) ->
{text, Value},
{keypress, true}]),

%% Ok and Cancel buttons
%% OK and Cancel buttons
W = Pad + Wlbl + Went + Pad,
{Wbtn, Hbtn} = dbg_ui_win:min_size(["Cancel"], 70, 30),
Ybtn = Pad + Hlbl + Pad,
Btn = gs:button(Win, [{x, Pad}, {y, Ybtn},
{width, Wbtn}, {height, Hbtn},
{label, {text,"Ok"}}, {font, Font}]),
{label, {text,"OK"}}, {font, Font}]),
gs:button(Win, [{x, W-Pad-Wbtn}, {y, Ybtn},
{width, Wbtn}, {height, Hbtn},
{label, {text,"Cancel"}}, {font, Font}]),
Expand Down Expand Up @@ -100,8 +100,8 @@ handle_event({gs, _Id, destroy, _Data, _Arg}, _WinInfo) ->
stopped;
handle_event({gs, Id, keypress, Data, ['Return'|_]}, WinInfo) ->
gs:config(WinInfo#winInfo.button, flash),
handle_event({gs, Id, click, Data, ["Ok"]}, WinInfo);
handle_event({gs, _Id, click, _Data, ["Ok"|_]}, WinInfo) ->
handle_event({gs, Id, click, Data, ["OK"]}, WinInfo);
handle_event({gs, _Id, click, _Data, ["OK"|_]}, WinInfo) ->
Ent = WinInfo#winInfo.entry,
Str = gs:read(Ent, text),
Type = WinInfo#winInfo.type,
Expand Down
2 changes: 1 addition & 1 deletion lib/debugger/src/dbg_ui_filedialog_win.erl
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ create_win(GS, Title, {X,Y}, Mode, Filter, Extra, FileName) ->
Opts = [{y, Y4}, {width, Wbtn}, {height, Hbtn}, {font, Font}],
case Mode of
normal ->
gs:button(Win, [{label, {text,"Ok"}}, {x, Pad},
gs:button(Win, [{label, {text,"OK"}}, {x, Pad},
{data, select} | Opts]),
gs:button(Win, [{label, {text,"Filter"}}, {x, Wlb/2-Wbtn/2},
{data, filter} | Opts]),
Expand Down
2 changes: 1 addition & 1 deletion lib/debugger/src/dbg_ui_interpret.erl
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,7 @@ interpret_all(State, Dir, [File0|Files]) ->
Window = dbg_ui_filedialog_win:get_window(State#state.win),
Error = format_error(int:interpretable(File)),
Msg = ["Error when interpreting:", File, Error,
"Ok to continue?"],
"OK to continue?"],
case tool_utils:confirm(Window, Msg) of
ok -> interpret_all(State, Dir, Files);
cancel -> true
Expand Down
2 changes: 1 addition & 1 deletion lib/debugger/src/dbg_ui_settings.erl
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,7 @@ default_settings_dir(GS) ->
{ok, CWD} = file:get_cwd(),

Msg = ["Default directory", DefDir, "does not exist.",
"Click Ok to create it or",
"Click OK to create it or",
"Cancel to use other directory."],
case tool_utils:confirm(GS, Msg) of
ok ->
Expand Down
30 changes: 15 additions & 15 deletions lib/debugger/src/dbg_wx_break_win.erl
Original file line number Diff line number Diff line change
Expand Up @@ -82,8 +82,8 @@ create_win(Parent, Pos, function, Mod, _Line) ->
wxComboBox:connect(Text, command_text_updated),
wxListBox:connect(LB, command_listbox_selected),
wxListBox:connect(LB, command_listbox_doubleclicked),
OkId = wxDialog:getAffirmativeId(Win),
OKButt = wxWindow:findWindowById(OkId, [{parent, Win}]),
OKId = wxDialog:getAffirmativeId(Win),
OKButt = wxWindow:findWindowById(OKId, [{parent, Win}]),
wxWindow:disable(OKButt),
wxDialog:centreOnParent(Win),
wxDialog:show(Win),
Expand Down Expand Up @@ -141,8 +141,8 @@ create_win(Parent, Pos, Type, Mod, Line) ->
wxComboBox:setFocus(ModT),
wxDialog:connect(Win, command_button_clicked),
wxDialog:connect(Win, command_text_updated),
OkId = wxDialog:getAffirmativeId(Win),
OKButt = wxWindow:findWindowById(OkId),
OKId = wxDialog:getAffirmativeId(Win),
OKButt = wxWindow:findWindowById(OKId),
wxWindow:disable(OKButt),
wxDialog:centreOnParent(Win),
wxDialog:show(Win),
Expand Down Expand Up @@ -180,30 +180,30 @@ handle_event(#wx{id=?wxID_CANCEL}, #winInfo{win=Win}) ->
wxDialog:destroy(Win),
stopped;
handle_event(#wx{event=#wxCommand{type=command_text_updated}},
#winInfo{type=function, text=Text, ok=Ok}) ->
#winInfo{type=function, text=Text, ok=OK}) ->
Module = wxComboBox:getValue(Text),
wxWindow:disable(Ok),
wxWindow:disable(OK),
{module, list_to_atom(Module)};
handle_event(#wx{event=#wxCommand{type=command_text_updated}},
#winInfo{text=Text, ok=Ok, entries=Es}) ->
#winInfo{text=Text, ok=OK, entries=Es}) ->
Module = wxComboBox:getValue(Text),
case check_input(Es) of
error -> wxWindow:disable(Ok);
_Data when Module =/= "" -> wxWindow:enable(Ok);
_ -> wxWindow:disable(Ok)
error -> wxWindow:disable(OK);
_Data when Module =/= "" -> wxWindow:enable(OK);
_ -> wxWindow:disable(OK)
end,
ignore;
handle_event(#wx{event=#wxCommand{type=command_listbox_selected}},
#winInfo{type=function, listbox=LB, ok=Ok}) ->
#winInfo{type=function, listbox=LB, ok=OK}) ->
case wxListBox:getSelections(LB) of
{N,_} when N > 0 -> wxWindow:enable(Ok);
_ -> wxWindow:disable(Ok)
{N,_} when N > 0 -> wxWindow:enable(OK);
_ -> wxWindow:disable(OK)
end,
ignore;
handle_event(#wx{id=OKorListBox, event=#wxCommand{type=OkorDoubleClick}},
handle_event(#wx{id=OKorListBox, event=#wxCommand{type=OKorDoubleClick}},
#winInfo{type=function,win=Win,listbox=LB,funcs=Funcs,text=Text})
when OKorListBox =:= ?wxID_OK;
OkorDoubleClick =:= command_listbox_doubleclicked ->
OKorDoubleClick =:= command_listbox_doubleclicked ->
Mod = wxComboBox:getValue(Text),
{_, IndexL} = wxListBox:getSelections(LB),
Breaks = [[list_to_atom(Mod)|lists:nth(Index+1, Funcs)] || Index <- IndexL],
Expand Down
2 changes: 1 addition & 1 deletion lib/debugger/src/dbg_wx_filedialog_win.erl
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ init([Parent, Id, Options0]) ->
Bott = wxDialog:createButtonSizer(Dlg, ?wxCANCEL bor ?wxOK),
wxDialog:connect(Dlg, command_button_clicked),

%% Ok done
%% OK done
Box = wxBoxSizer:new(?wxVERTICAL),
wxSizer:add(Box, Top, [{border, 2}, {flag,?wxALL bor ?wxEXPAND}]),
wxSizer:add(Box, Dir, [{border, 2}, {flag,?wxALL bor ?wxEXPAND}]),
Expand Down
2 changes: 1 addition & 1 deletion lib/debugger/src/dbg_wx_settings.erl
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ default_settings_dir(Win) ->
{ok, CWD} = file:get_cwd(),

Msg = ["Default directory ", DefDir, " does not exist. ",
"Click Ok to create it or ",
"Click OK to create it or ",
"Cancel to use other directory."],
case dbg_wx_win:confirm(Win, Msg) of
ok ->
Expand Down

0 comments on commit 84d0304

Please sign in to comment.