File 0869-Fix-typos-in-lib-wx.patch of Package erlang

From 3b7a02bb33e08180bd3fa90ac91382b1c7c4266a Mon Sep 17 00:00:00 2001
From: Kian-Meng Ang <kianmeng@cpan.org>
Date: Thu, 6 Jan 2022 21:48:36 +0800
Subject: [PATCH] Fix typos in lib/wx

---
 lib/wx/api_gen/README                      | 2 +-
 lib/wx/api_gen/apidiff.escript             | 2 +-
 lib/wx/api_gen/gl_gen_erl.erl              | 2 +-
 lib/wx/api_gen/wx_doxygen.conf             | 2 +-
 lib/wx/api_gen/wx_extra/added_func.h       | 4 ++--
 lib/wx/api_gen/wx_extra/wxEvtHandler.erl   | 4 ++--
 lib/wx/api_gen/wx_extra/wxe_evth.h         | 2 +-
 lib/wx/api_gen/wx_gen.erl                  | 4 ++--
 lib/wx/api_gen/wx_gen.hrl                  | 2 +-
 lib/wx/api_gen/wxapi.conf                  | 4 ++--
 lib/wx/c_src/egl_impl.c                    | 4 ++--
 lib/wx/c_src/wxe_callback_impl.cpp         | 2 +-
 lib/wx/c_src/wxe_helpers.cpp               | 4 ++--
 lib/wx/c_src/wxe_impl.cpp                  | 2 +-
 lib/wx/c_src/wxe_nif.h                     | 2 +-
 lib/wx/doc/src/notes.xml                   | 6 +++---
 lib/wx/examples/demo/demo_html_tagger.erl  | 2 +-
 lib/wx/examples/demo/ex_sashWindow.erl     | 2 +-
 lib/wx/examples/demo/ex_sizers.erl         | 4 ++--
 lib/wx/examples/demo/ex_splitterWindow.erl | 6 +++---
 lib/wx/examples/simple/menu.erl            | 2 +-
 lib/wx/examples/simple/minimal.erl         | 2 +-
 lib/wx/src/gen/glu.erl                     | 2 +-
 lib/wx/src/wxe_master.erl                  | 2 +-
 lib/wx/test/wx_basic_SUITE.erl             | 2 +-
 lib/wx/test/wx_class_SUITE.erl             | 2 +-
 lib/wx/test/wx_opengl_SUITE.erl            | 2 +-
 lib/wx/test/wx_xtra_SUITE.erl              | 6 +++---
 28 files changed, 41 insertions(+), 41 deletions(-)

diff --git a/lib/wx/api_gen/README b/lib/wx/api_gen/README
index 394469030c..364dbdd9f2 100644
--- a/lib/wx/api_gen/README
+++ b/lib/wx/api_gen/README
@@ -15,7 +15,7 @@ CONFIGURATION:
 
     Adding/changing stuff/classes should be done by updating wxapi.conf
     and running make. Sometimes the code generator will require changes,
-    I havn't thought of everything yet.
+    I haven't thought of everything yet.
 
 RUNNING:
     I use the following alias wxgen='make WXGTK_DIR=/opt/local/include/wx-2.8/ GL_DIR=/home/dgud/opengl'
diff --git a/lib/wx/api_gen/gl_gen_erl.erl b/lib/wx/api_gen/gl_gen_erl.erl
index fa5ce4a91f..bf3fdee1a6 100644
--- a/lib/wx/api_gen/gl_gen_erl.erl
+++ b/lib/wx/api_gen/gl_gen_erl.erl
@@ -149,7 +149,7 @@ glu_api(Fs) ->
     %% w("%%  VertexPos  = binary()~n",[]),
     w("%% @doc General purpose polygon triangulation.~n",[]),
     w("%% The first argument is the normal and the second a list of~n"
-      "%% vertex positions. Returned is a list of indecies of the vertices~n"
+      "%% vertex positions. Returned is a list of indices of the vertices~n"
       "%% and a binary (64bit native float) containing an array of~n"
       "%% vertex positions, it starts with the vertices in Vs and~n"
       "%% may contain newly created vertices in the end.~n", []),
diff --git a/lib/wx/api_gen/wx_extra/bugs.h b/lib/wx/api_gen/wx_extra/bugs.h
index 654cc8b430..d3d8527976 100644
--- a/lib/wx/api_gen/wx_extra/bugs.h
+++ b/lib/wx/api_gen/wx_extra/bugs.h
@@ -15,7 +15,7 @@ class WXDLLIMPEXP_XRC wxXmlResource : public wxObject
    wxObject xrcctrl(wxWindow *Window, wxString Name, wxString Type);
 };
 
-// The generater needs constructors
+// The generator needs constructors
 class WXDLLIMPEXP_ADV wxGridCellBoolRenderer : public wxGridCellRenderer
 {
  public:
diff --git a/lib/wx/api_gen/wx_extra/wxEvtHandler.erl b/lib/wx/api_gen/wx_extra/wxEvtHandler.erl
index 8d0d97e8f0..8c1e4279a3 100644
--- a/lib/wx/api_gen/wx_extra/wxEvtHandler.erl
+++ b/lib/wx/api_gen/wx_extra/wxEvtHandler.erl
@@ -16,7 +16,7 @@
 %% Beware that the callback will be in executed in new process each time.
 %%
 %% <a href="http://www.wxwidgets.org/manuals/stable/wx_wxevthandler.html">
-%% The orginal documentation</a>. 
+%% The original documentation</a>. 
 %%
 %%
 -module(wxEvtHandler).
@@ -52,7 +52,7 @@ connect(This, EventType) ->
 %%                          This is not used if the 'callback' option is used. 
 %%                          Default false.
 %%    {callback, function()} Use a callback fun(EventRecord::wx(), EventObject::wxObject()) 
-%%                          to process the event. Default not specfied i.e. a message will
+%%                          to process the event. Default not specified i.e. a message will
 %%                          be delivered to the process calling this function.
 %%    {userData, term()}    An erlang term that will be sent with the event. Default: [].
 -spec connect(This::wxEvtHandler(), EventType::wxEventType(), [Option]) -> ok when
diff --git a/lib/wx/api_gen/wx_gen.erl b/lib/wx/api_gen/wx_gen.erl
index 8f22bfc850..dbe1997921 100644
--- a/lib/wx/api_gen/wx_gen.erl
+++ b/lib/wx/api_gen/wx_gen.erl
@@ -648,7 +648,7 @@ parse_param(#xmlElement{name=declname,content=[C]},_Opts,T) ->
 parse_param(#xmlElement{name=defval,content=[#xmlText{value=Def}]},_Opts,T) -> 
     T#param{def=string:strip(Def)};
 parse_param(#xmlElement{name=defval,content=Other},_Opts,T) -> 
-    %% For defaults = (modifer wxType *) NULL 
+    %% For defaults = (modifier wxType *) NULL 
     Def0 = foldr(fun(#xmlText{value=V}, Acc) -> V ++ Acc;
 		    (#xmlElement{content=[#xmlText{value=V}]},Acc) -> 
 			 V ++ Acc
@@ -1522,7 +1522,7 @@ drop_empty(List) ->
 parse_enums(Files) ->
     DontSearch = ["wxchar","filefn", "platform", "strconv", "filename", 
 		  "buffer", "string", "debug", "platinfo"],
-    %% Arg need to patch some specials, atleast for wx-2.6
+    %% Arg need to patch some specials, at least for wx-2.6
     ExtraSearch = ["gtk_2glcanvas", "generic_2splash"],
     parse_enums(Files ++ ExtraSearch,gb_sets:from_list(DontSearch)).
 
diff --git a/lib/wx/api_gen/wx_gen.hrl b/lib/wx/api_gen/wx_gen.hrl
index 252de3d0c9..ede3b56212 100644
--- a/lib/wx/api_gen/wx_gen.hrl
+++ b/lib/wx/api_gen/wx_gen.hrl
@@ -26,7 +26,7 @@
 	  file    = undefined,
 	  options  = undefined,
 	  abstract = false,
-	  id,                      % Unique integer identifer
+	  id,                      % Unique integer identifier
 	  doc
 	 }).
 
diff --git a/lib/wx/api_gen/wxapi.conf b/lib/wx/api_gen/wxapi.conf
index ac1fc9c9cd..b9077702ee 100644
--- a/lib/wx/api_gen/wxapi.conf
+++ b/lib/wx/api_gen/wxapi.conf
@@ -1501,7 +1501,7 @@
   'RightDockable','Row','SafeSet','SetFlag','Show','ToolbarPane',
   'Top','TopDockable','Window',
   %% Extended func
-  %% These are not initilized by default and thus cause crashes
+  %% These are not initialized by default and thus cause crashes
   %% {'GetName',
   %%  [{pre_hook, [{c, "#if 0\n"}]},
   %%   {post_hook, [{c, "#endif\n if(!This) throw wxe_badarg(0);\n wxString Result = This->name"}]}]},
@@ -2260,7 +2260,7 @@
 
 {class, wxTaskBarIcon, wxEvtHandler, [],
  [wxTaskBarIcon,'~wxTaskBarIcon',
-  %%'CreatePopupMenu', virtual overrided is a callback
+  %%'CreatePopupMenu', virtual overridded is a callback
   %% 'IsIconInstalled', 'IsOk', not available on mac
   'PopupMenu','RemoveIcon','SetIcon']}.
 
diff --git a/lib/wx/c_src/egl_impl.cpp b/lib/wx/c_src/egl_impl.cpp
index 2703f55408..55f06b259e 100644
--- a/lib/wx/c_src/egl_impl.cpp
+++ b/lib/wx/c_src/egl_impl.cpp
@@ -279,7 +279,7 @@ int egl_load_functions() {
 }
 
 /* *******************************************************************************
- * GLU Tesselation special
+ * GLU Tessellation special
  * ******************************************************************************/
 
 static GLUtesselator* tess;
@@ -355,7 +355,7 @@ egl_ogla_error(GLenum errorCode)
 {
   // const GLubyte *err;
   // err = gluErrorString(errorCode);
-  // fprintf(stderr, "Tesselation error: %d: %s\r\n", (int) errorCode, err);
+  // fprintf(stderr, "Tessellation error: %d: %s\r\n", (int) errorCode, err);
 }
 
 void init_tess()
diff --git a/lib/wx/c_src/wxe_callback_impl.cpp b/lib/wx/c_src/wxe_callback_impl.cpp
index 50f6c0166c..e042f00e13 100644
--- a/lib/wx/c_src/wxe_callback_impl.cpp
+++ b/lib/wx/c_src/wxe_callback_impl.cpp
@@ -46,7 +46,7 @@ wxeEvtListener::wxeEvtListener(ErlNifPid caller, int req, ERL_NIF_TERM req_type,
 }
 
 wxeEvtListener::~wxeEvtListener() {
-    // fprintf(stderr, "CBD Deleteing %p %s\r\n", this, class_name); fflush(stderr);
+    // fprintf(stderr, "CBD Deleting %p %s\r\n", this, class_name); fflush(stderr);
   if(user_data) {
     delete user_data;
   }
diff --git a/lib/wx/c_src/wxe_impl.cpp b/lib/wx/c_src/wxe_impl.cpp
index 9786572ef6..61eea2e8c2 100644
--- a/lib/wx/c_src/wxe_impl.cpp
+++ b/lib/wx/c_src/wxe_impl.cpp
@@ -632,7 +632,7 @@ void WxeApp::destroyMemEnv(wxeMetaCommand &Ecmd)
 	    delete refd;
 	    ptr2ref.erase(it);
 	  } // overridden allocs deletes meta-data in clearPtr
-	} else { // Not alloced in erl just delete references
+	} else { // Not allocated in erl just delete references
 	  if(refd->ref >= global_me->next) { // if it is not part of global ptrs
 	    delete refd;
 	    ptr2ref.erase(it);
diff --git a/lib/wx/doc/src/notes.xml b/lib/wx/doc/src/notes.xml
index af72001c24..2a24d3790a 100644
--- a/lib/wx/doc/src/notes.xml
+++ b/lib/wx/doc/src/notes.xml
@@ -996,7 +996,7 @@
         <item>
           <p>
 	    Wx on MacOS X generated complains on stderr about certain
-	    cocoa functions not beeing called from the "Main thread".
+	    cocoa functions not being called from the "Main thread".
 	    This is now corrected.</p>
           <p>
 	    Own Id: OTP-9081</p>
@@ -1174,7 +1174,7 @@
       <list>
         <item>
             <p>wxHtmlWindow class implemented.</p> <p>All exceptions
-            from callbacks are now catched and written to the
+            from callbacks are now caught and written to the
             log.</p> <p>Some defines where wrong in 'wx.hrl'.</p>
             <p><c>wx:batch/1</c> and friends could hang forever if
             for instance a breakpoint was set inside the fun. That
diff --git a/lib/wx/examples/demo/demo_html_tagger.erl b/lib/wx/examples/demo/demo_html_tagger.erl
index cc24cbaa67..d0137259f1 100644
--- a/lib/wx/examples/demo/demo_html_tagger.erl
+++ b/lib/wx/examples/demo/demo_html_tagger.erl
@@ -23,7 +23,7 @@
 %% That's because this program uses some pretty dodgy techniques to
 %% get at the data it requires.
 
-%% I use epp_dodger to parse the file and the new imporved erl_scan
+%% I use epp_dodger to parse the file and the new improved erl_scan
 %% find the exact values of the tokens
 
 %% epp_dodger returns an objects of type erl_syntax which are pretty
diff --git a/lib/wx/examples/demo/ex_sashWindow.erl b/lib/wx/examples/demo/ex_sashWindow.erl
index 63528f65d1..7ff85b442c 100644
--- a/lib/wx/examples/demo/ex_sashWindow.erl
+++ b/lib/wx/examples/demo/ex_sashWindow.erl
@@ -65,7 +65,7 @@ do_init(Config) ->
     Win2 = wxPanel:new(BottomSash, []),
     wxStaticText:new(Win2, ?wxID_ANY, "This is the bottom sash", []),
 
-    %% Make the bottom edge of the top sash dragable
+    %% Make the bottom edge of the top sash draggable
     wxSashWindow:setSashVisible(TopSash, ?wxSASH_BOTTOM, true),
     wxPanel:connect(Panel, sash_dragged),
     wxPanel:connect(Panel, size),
diff --git a/lib/wx/examples/demo/ex_sizers.erl b/lib/wx/examples/demo/ex_sizers.erl
index 800f17f014..50e3bd3320 100644
--- a/lib/wx/examples/demo/ex_sizers.erl
+++ b/lib/wx/examples/demo/ex_sizers.erl
@@ -59,7 +59,7 @@ do_init(Config) ->
 	       "Weighting Factor",
 	       "Edge Affinity",
 	       "Spacer",
-	       "Centering In Avalible Space",
+	       "Centering In Available Space",
 	       "Simple Border",
 	       "East And West Border",
 	       "North And South Border",
@@ -149,7 +149,7 @@ create_example(Parent, Example) ->
 		north_and_south_border(Panel);
 	    "Simple Border" ->
 		simple_border(Panel);
-	    "Centering In Avalible Space" ->
+	    "Centering In Available Space" ->
 		centering_in_avalible_space(Panel);
 	    "Spacer" ->
 		spacer(Panel);
diff --git a/lib/wx/examples/demo/ex_splitterWindow.erl b/lib/wx/examples/demo/ex_splitterWindow.erl
index 14f63600a3..0946a73229 100644
--- a/lib/wx/examples/demo/ex_splitterWindow.erl
+++ b/lib/wx/examples/demo/ex_splitterWindow.erl
@@ -54,14 +54,14 @@ do_init(Config) ->
 
     Splitter = wxSplitterWindow:new(Panel, []),
 
-    Win1 = wxTextCtrl:new(Splitter, 1, [{value, "Splitted Window 1"},
+    Win1 = wxTextCtrl:new(Splitter, 1, [{value, "Split Window 1"},
         			       {style, ?wxDEFAULT bor ?wxTE_MULTILINE}]),
-    Win2 = wxTextCtrl:new(Splitter, 1, [{value, "Splitted Window 1"},
+    Win2 = wxTextCtrl:new(Splitter, 1, [{value, "Split Window 1"},
 					{style, ?wxDEFAULT bor ?wxTE_MULTILINE}]),
 
     wxSplitterWindow:splitVertically(Splitter, Win1, Win2),
     wxSplitterWindow:setSashGravity(Splitter,   0.5),
-    %% Set pane-size =/= 0 to not unsplit on doubleclick
+    %% Set pane-size =/= 0 to not unsplit on double-click
     %% on the splitter
     wxSplitterWindow:setMinimumPaneSize(Splitter,50),
     
diff --git a/lib/wx/examples/simple/menu.erl b/lib/wx/examples/simple/menu.erl
index 829c88a3d5..5477f6c921 100644
--- a/lib/wx/examples/simple/menu.erl
+++ b/lib/wx/examples/simple/menu.erl
@@ -309,7 +309,7 @@ create_help_menu() ->
     HelpMenu =  wxMenu:new(),
     % unlike wxwidgets the stock menu items still need text to be given, 
     % although help text does appear
-    % Note the keybord accelerator
+    % Note the keyboard accelerator
     wxMenu:append(HelpMenu, wxMenuItem:new([
             {id,    ?menuID_HELP_ABOUT},
             %{text,  "&About\tF1"},
diff --git a/lib/wx/examples/simple/minimal.erl b/lib/wx/examples/simple/minimal.erl
index 45efc06462..6011bbbc8b 100644
--- a/lib/wx/examples/simple/minimal.erl
+++ b/lib/wx/examples/simple/minimal.erl
@@ -55,7 +55,7 @@ create_window(Wx) ->
     % unlike wxwidgets the stock menu items still need text to be given, 
     % although help text does appear
     _QuitMenuItem  = wxMenu:append(FileM, ?wxID_EXIT, "&Quit"),
-    % Note the keybord accelerator
+    % Note the keyboard accelerator
     _AboutMenuItem = wxMenu:append(HelpM, ?wxID_ABOUT, "&About...\tF1"),
 
     wxMenu:appendSeparator(HelpM),    
diff --git a/lib/wx/src/gen/glu.erl b/lib/wx/src/gen/glu.erl
index 6d4d390205..9c48a03b26 100644
--- a/lib/wx/src/gen/glu.erl
+++ b/lib/wx/src/gen/glu.erl
@@ -55,7 +55,7 @@
 
 %% @doc General purpose polygon triangulation.
 %% The first argument is the normal and the second a list of
-%% vertex positions. Returned is a list of indecies of the vertices
+%% vertex positions. Returned is a list of indices of the vertices
 %% and a binary (64bit native float) containing an array of
 %% vertex positions, it starts with the vertices in Vs and
 %% may contain newly created vertices in the end.
diff --git a/lib/wx/src/wxe_master.erl b/lib/wx/src/wxe_master.erl
index c3496a0026..24a122663e 100644
--- a/lib/wx/src/wxe_master.erl
+++ b/lib/wx/src/wxe_master.erl
@@ -74,7 +74,7 @@ init_env(SilentStart) ->
 
 
 %%--------------------------------------------------------------------
-%% Initalizes the opengl library
+%% Initializes the opengl library
 %%--------------------------------------------------------------------
 init_opengl() ->
     GLLib = wxe_util:wxgl_dl(),
diff --git a/lib/wx/test/wx_basic_SUITE.erl b/lib/wx/test/wx_basic_SUITE.erl
index de86a8362b..fa77c37f15 100644
--- a/lib/wx/test/wx_basic_SUITE.erl
+++ b/lib/wx/test/wx_basic_SUITE.erl
@@ -607,7 +607,7 @@ check_events([{sync_event, #wx{event=#wxPaint{}}, Obj}|Rest], Async, Sync) ->
     ?mt(wxPaintEvent, Obj),
     check_events(Rest, Async, Sync+1);
 check_events([], Async, Sync) ->
-    case Async > 0 of  %% Test sync explictly
+    case Async > 0 of  %% Test sync explicitly
 	true -> ok;
 	false -> {Async, Sync}
     end.
diff --git a/lib/wx/test/wx_class_SUITE.erl b/lib/wx/test/wx_class_SUITE.erl
index b7c036e6da..794fd947a5 100644
--- a/lib/wx/test/wx_class_SUITE.erl
+++ b/lib/wx/test/wx_class_SUITE.erl
@@ -87,7 +87,7 @@ calendarCtrl(Config) ->
 	true ->
 	    ?log("DateAttr is null~n",[]);
 	false ->
-	    ?log("DateAttr is useable~n",[]),
+	    ?log("DateAttr is usable~n",[]),
 	    DateAttr = ?mt(wxCalendarDateAttr, wxCalendarDateAttr:new()),
 	    wxCalendarDateAttr:setBackgroundColour(DateAttr, {0,243,0}),
 	    wxCalendarCtrl:setAttr(Cal, Day, DateAttr),
diff --git a/lib/wx/test/wx_opengl_SUITE.erl b/lib/wx/test/wx_opengl_SUITE.erl
index 28c5b70383..443dc3b05b 100644
--- a/lib/wx/test/wx_opengl_SUITE.erl
+++ b/lib/wx/test/wx_opengl_SUITE.erl
@@ -88,7 +88,7 @@ end_per_group(_GroupName, Config) ->
 	 {{7,8,3,2},{0,-1,0}}]).
 
 
-%% Test we can create a glCanvas and that functions are loaded dynamicly
+%% Test we can create a glCanvas and that functions are loaded dynamically
 canvas(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 canvas(Config) ->
     WX = ?mr(wx_ref, wx:new()),
diff --git a/lib/wx/test/wx_xtra_SUITE.erl b/lib/wx/test/wx_xtra_SUITE.erl
index a87f4a83b1..2b35c2c660 100644
--- a/lib/wx/test/wx_xtra_SUITE.erl
+++ b/lib/wx/test/wx_xtra_SUITE.erl
@@ -68,7 +68,7 @@ end_per_group(_GroupName, Config) ->
 %%  before wx:destroy is called.
 destroy_app(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 destroy_app(_Config) ->
-    %% This is timing releated but we test a couple of times
+    %% This is timing related but we test a couple of times
     wx_test_lib:flush(),
     ?m(ok, destroy_app_test(15)).
 
@@ -102,7 +102,7 @@ destroy_app_test(_) ->
     end.
 
 
-%% This should work, and does but not when run automaticly on windows 
+%% This should work, and does but not when run automatically on windows 
 %% for some strange reason (it just hangs), run it last.
 app_dies(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 app_dies(_Config) ->
@@ -160,7 +160,7 @@ oops(Die, Line) when (Die =:= last) orelse (Die =< Line) ->
 oops(_,_) -> ok.
 
 
-%% This have happend often enough that I have special code to handle 
+%% This have happened often enough that I have special code to handle 
 %% this user error (i.e. using the a window twice in an sizer).
 multiple_add_in_sizer(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 multiple_add_in_sizer(Config) ->
-- 
2.31.1

openSUSE Build Service is sponsored by