File 1350-Fix-typos-in-lib-odbc.patch of Package erlang

From a17892f5d06e09e31634bbd20909475d702b3568 Mon Sep 17 00:00:00 2001
From: "Kian-Meng, Ang" <kianmeng@cpan.org>
Date: Thu, 23 Dec 2021 15:22:09 +0800
Subject: [PATCH] Fix typos in lib/odbc

---
 lib/odbc/c_src/odbcserver.c            | 32 +++++++++++++-------------
 lib/odbc/doc/src/odbc.xml              | 12 +++++-----
 lib/odbc/src/odbc.erl                  | 12 +++++-----
 lib/odbc/src/odbc_debug.erl            |  2 +-
 lib/odbc/test/odbc_connect_SUITE.erl   | 14 +++++------
 lib/odbc/test/odbc_data_type_SUITE.erl |  2 +-
 lib/odbc/test/odbc_query_SUITE.erl     |  4 ++--
 lib/odbc/test/oracle.erl               |  2 +-
 8 files changed, 40 insertions(+), 40 deletions(-)

diff --git a/lib/odbc/c_src/odbcserver.c b/lib/odbc/c_src/odbcserver.c
index 2e0ada4f30..5a01630cbc 100644
--- a/lib/odbc/c_src/odbcserver.c
+++ b/lib/odbc/c_src/odbcserver.c
@@ -29,7 +29,7 @@
   by sendig a shutdown request to the supervisor thread.
 
   Erlang will start this c-process as a port-program and send information
-  regarding inet-port nummbers through the erlang-port.
+  regarding inet-port numbers through the erlang-port.
   After that c-process will communicate via sockets with erlang. The
   reason for this is that some odbc-drivers do unexpected things with
   stdin/stdout messing up the erlang-port communication.
@@ -41,7 +41,7 @@
    Bytes, StringTerminator]
    
    CommandByte - constants between 0 and 255
-   identifing the request defined in odbc_internal.hrl and odbcserver.h
+   identifying the request defined in odbc_internal.hrl and odbcserver.h
 
    Bytes - How to interpret this sequence of bytes depends on the
    CommandByte.
@@ -208,7 +208,7 @@ static void tcp_nodelay(int sock);
 #endif
 static void clean_socket_lib(void);
 
-/*------------- Memory handling funtions --------------------------------*/
+/*------------- Memory handling functions --------------------------------*/
 
 static void * safe_malloc(int size);
 static void * safe_realloc(void * ptr, int size);
@@ -218,7 +218,7 @@ static void free_params(param_array **params, int cols);
 static void clean_state(db_state *state);
 static SQLLEN* alloc_strlen_indptr(int n, int val);
 
-/* ------------- Init/map/bind/retrive functions -------------------------*/
+/* ------------- Init/map/bind/retrieve functions -------------------------*/
 
 static void init_driver(int erl_auto_commit_mode, int erl_trace_driver,
 			   db_state *state);
@@ -396,7 +396,7 @@ DWORD WINAPI database_handler(const char *port)
 }
  
 /* Description: Calls the appropriate function to handle the database
-   request recived from the erlang-process. Returns a message to send back
+   request received from the erlang-process. Returns a message to send back
    to erlang. */
 static db_result_msg handle_db_request(byte *reqstring, db_state *state)
 {
@@ -674,12 +674,12 @@ static db_result_msg db_query(byte *sql, db_state *state)
 	do {
 	    ei_x_encode_list_header(&dynamic_buffer(state), 1);
 	    msg = encode_result(state);
-	    /* We don't want to continue if an error occured */
+	    /* We don't want to continue if an error occurred */
 	    if (msg.length != 0) { 
 		break;
 	    }
 	    msg = more_result_sets(state);
-	    /* We don't want to continue if an error occured */
+	    /* We don't want to continue if an error occurred */
 	    if (msg.length != 0) { 
 		break;
 	    }
@@ -749,7 +749,7 @@ static db_result_msg db_select_count(byte *sql, db_state *state)
 }
 
 /* Description: Fetches rows from the result set associated with the
-   connection by db_select_count. The method of seletion will be according
+   connection by db_select_count. The method of selection will be according
    too <args> */
 static db_result_msg db_select(byte *args, db_state *state)
 {
@@ -1068,7 +1068,7 @@ static db_result_msg encode_error_message(char *reason, char *errCode, SQLINTEGE
     return msg;
 }
 
-/* Description: Encode a messge that is a erlang atom */
+/* Description: Encode a message that is a erlang atom */
 static db_result_msg encode_atom_message(char* atom)
 {
     int index;
@@ -1148,7 +1148,7 @@ static db_result_msg encode_result(db_state *state)
 	    do {
 		num_of_rows = num_of_rows + (int)RowCountPtr;
 		msg = more_result_sets(state);
-		/* We don't want to continue if an error occured */
+		/* We don't want to continue if an error occurred */
 		if (msg.length != 0) { 
 		    return msg;
 		}
@@ -1344,7 +1344,7 @@ static db_result_msg encode_column_name_list(SQLSMALLINT num_of_columns,
 		    (char *)safe_malloc(columns(state)[i].type.len);
 	
 		if (columns(state)[i].type.c == SQL_C_BINARY) {
-		    /* retrived later by retrive_binary_data */
+		    /* retrieved later by retrive_binary_data */
 		} else {
 		    if(!sql_success(
 			SQLBindCol
@@ -2075,7 +2075,7 @@ static void clean_socket_lib(void)
 }
     
 
-/*------------- Memmory handling funtions -------------------------------*/
+/*------------- Memory handling functions -------------------------------*/
 static void *safe_malloc(int size)
 {
     void *memory;
@@ -2172,7 +2172,7 @@ static SQLLEN* alloc_strlen_indptr(int n, int val)
     return arr;
 }
 
-/* ------------- Init/map/bind/retrive functions  ------------------------*/
+/* ------------- Init/map/bind/retrieve functions  ------------------------*/
 
 /* Prepare the state for a connection */
 static void init_driver(int erl_auto_commit_mode, int erl_trace_driver,
@@ -2410,7 +2410,7 @@ static void init_param_statement(int cols, SQLLEN num_param_values,
     }
 
     /* Note the (SQLLEN *) cast is correct as the API function SQLSetStmtAttr
-       takes either an interger or a pointer depending on the attribute */
+       takes either an integer or a pointer depending on the attribute */
     if(!sql_success(SQLSetStmtAttr(statement_handle(state),
 				   SQL_ATTR_PARAMSET_SIZE,
 				   (SQLLEN *)num_param_values,
@@ -2739,8 +2739,8 @@ static Boolean sql_success(SQLRETURN result)
 
 /* Description: An ODBC function can post zero or more diagnostic records
    each time it is called. This function loops through the current set of
-   diagnostic records scaning for error messages and the sqlstate.
-   If this function is called when no error has ocurred only the sqlState
+   diagnostic records scanning for error messages and the sqlstate.
+   If this function is called when no error has occurred only the sqlState
    field may be referenced.*/
 static diagnos get_diagnos(SQLSMALLINT handleType, SQLHANDLE handle, Boolean extendedErrors)
 {
diff --git a/lib/odbc/doc/src/odbc.xml b/lib/odbc/doc/src/odbc.xml
index a1d3184acf..28d4334fdf 100644
--- a/lib/odbc/doc/src/odbc.xml
+++ b/lib/odbc/doc/src/odbc.xml
@@ -176,7 +176,7 @@
 	  <p>The default timeout is infinity </p>
 	  
 	  <p> >If the option binary_strings is turned on all strings
-	  will be returned as binaries and strings inputed to
+	  will be returned as binaries and strings inputted to
 	  param_query will be expected to be binaries. The user needs
 	  to ensure that the binary is in an encoding that the
 	  database expects. By default this option is turned off.</p>
@@ -193,7 +193,7 @@
           connection, limiting the API but gaining speed.</p>
 
 	  <note><p>Turning the scrollable_cursors option off is noted
-	  to make old odbc-drivers able to connect that will otherwhise fail.</p></note>
+	  to make old odbc-drivers able to connect that will otherwise fail.</p></note>
 	  
         <p>If trace mode is turned on this tells the ODBC driver to
           write a trace log to the file SQL.LOG that is placed in the
@@ -210,14 +210,14 @@
 
 		  <p>The <c>extended_errors</c> option enables extended ODBC error
 			  information when an operation fails. Rather than returning <c>{error, Reason}</c>,
-			  the failing function will reutrn <c>{error, {ODBCErrorCode, NativeErrorCode, Reason}}</c>.
+			  the failing function will return <c>{error, {ODBCErrorCode, NativeErrorCode, Reason}}</c>.
 			  Note that this information is probably of little use when writing database-independent code,
 			  but can be of assistance in providing more sophisticated error handling when dealing with
 			  a known underlying database.
 	           </p>
 			 <list type="bulleted">
 				  <item><c>ODBCErrorCode</c> is the ODBC error string returned by the ODBC driver.</item>
-				  <item><c>NativeErrorCode</c> is the numberic error code returned by the underlying database. The possible values
+				  <item><c>NativeErrorCode</c> is the numeric error code returned by the underlying database. The possible values
 					  and their meanings are dependent on the database being used.</item>
 				  <item><c>Reason</c> is as per the <c>Reason</c> field when extended errors are not enabled.</item>
 		  </list>
@@ -225,7 +225,7 @@
         <note>
             <p>The current implementation spawns a port program
             written in C that utilizes the actual ODBC driver. There
-            is a default timeout of 5000 msec for this port programm
+            is a default timeout of 5000 msec for this port program
             to connect to the Erlang ODBC application. This timeout
             can be changed by setting an application specific
             environment variable 'port_timeout' with the number of
@@ -260,7 +260,7 @@
       <fsummary>Queries the database to find out the data types of the columns of the table <c>Table</c>. </fsummary>
       <type>
         <v>Ref = connection_reference()</v>
-        <v>Table = string() - Name of databas table.</v>
+        <v>Table = string() - Name of database table.</v>
         <v>TimeOut = time_out()</v>
         <v>Description = [{col_name(), odbc_data_type()}]</v>
         <v>Reason = common_reason()</v>
diff --git a/lib/odbc/src/odbc.erl b/lib/odbc/src/odbc.erl
index 8871acd3f4..892e3b041c 100644
--- a/lib/odbc/src/odbc.erl
+++ b/lib/odbc/src/odbc.erl
@@ -52,7 +52,7 @@
 		owner,                       % Pid of the connection owner
 		result_set = undefined,      % exists | undefined
 		auto_commit_mode = on,       % on | off
-		%% Indicates if first, last and "select absolut"
+		%% Indicates if first, last and "select absolute"
 		%% is supported by the odbc driver.
 		absolute_pos,                % true | false  
 		%% Indicates if prev and "select relative"
@@ -129,11 +129,11 @@ disconnect(ConnectionReference) when is_pid(ConnectionReference)->
     case call(ConnectionReference, {disconnect, ODBCCmd}, 5000) of 
 	{error, connection_closed} ->
 	    %% If the connection has already been closed the effect of
-	    %% disconnect has already been acomplished
+	    %% disconnect has already been accomplished
 	    ok; 
 	%% Note a time out of this call will return ok, as disconnect
 	%% will always succeed, the time out is to make sure
-	%% the connection is killed brutaly if it will not be shut down
+	%% the connection is killed brutally if it will not be shut down
 	%% gracefully.
 	ok ->
 	    ok;
@@ -603,7 +603,7 @@ handle_msg({select_cmd, _Type, _ODBCCmd}, _Timeout, State) ->
     {reply, Reply, State#state{reply_to = undefined}};
 
 %---------------------------------------------------------------------------
-%% Catch all -  This can oly happen if the application programmer writes 
+%% Catch all -  This can only happen if the application programmer writes 
 %% really bad code that violates the API.
 handle_msg(Request, _Timeout, State) ->
     {stop, {'API_violation_connection_colsed', Request},
@@ -624,7 +624,7 @@ handle_cast(Msg, State) ->
 %%--------------------------------------------------------------------------
 %% handle_info(Msg, State) -> {noreply, State} | {noreply, State, Timeout} |
 %%			      {stop, Reason, State}
-%% Description: Handles timouts, replys from the port-program and EXIT and
+%% Description: Handles timouts, replies from the port-program and EXIT and
 %%		down messages.
 %% Note: The order of the function clauses is significant.
 %%--------------------------------------------------------------------------
@@ -745,7 +745,7 @@ handle_info({'EXIT', Port, _}, State = #state{erlang_port = Port,
 handle_info({'EXIT', Port, Reason}, State = #state{erlang_port = Port}) ->
     {stop, Reason, State};
 
-%%% If the owning process dies there is no reson to go on
+%%% If the owning process dies there is no reason to go on
 handle_info({'DOWN', _Ref, _Type, _Process, normal}, State) ->
     {stop, normal, State#state{reply_to = undefined}};
     
diff --git a/lib/odbc/src/odbc_debug.erl b/lib/odbc/src/odbc_debug.erl
index a2e5e5dff3..9a55f6c3ad 100644
--- a/lib/odbc/src/odbc_debug.erl
+++ b/lib/odbc/src/odbc_debug.erl
@@ -18,7 +18,7 @@
 %%	Process  - pid() | Name | {global, Name} | {Name, Node} 
 %%	OnOff   - on | off
 %%      Level   - exported | all
-%% Description: Turns on tracing of messages sent and recived by
+%% Description: Turns on tracing of messages sent and received by
 %%              the server <Process> and tracing on all, or all exported 
 %%              functions, according to level <Level>, in this module.
 %%              Result will be printed on stdout.
diff --git a/lib/odbc/test/odbc_connect_SUITE.erl b/lib/odbc/test/odbc_connect_SUITE.erl
index 714a0cb776..522ccc805e 100644
--- a/lib/odbc/test/odbc_connect_SUITE.erl
+++ b/lib/odbc/test/odbc_connect_SUITE.erl
@@ -254,7 +254,7 @@ not_exist_db() ->
 not_exist_db(_Config)  ->
     {error, _} = odbc:connect("DSN=foo;UID=bar;PWD=foobar",
 			      odbc_test_lib:platform_options()),
-    %% So that the odbc control server can be stoped "in the correct way"
+    %% So that the odbc control server can be stopped "in the correct way"
     ct:sleep(100).
 
 %%-------------------------------------------------------------------------
@@ -439,7 +439,7 @@ connect_port_timeout(Config) when is_list(Config) ->
 %%-------------------------------------------------------------------------
 timeout() ->
     [{"Test that timeouts don't cause unwanted behavior sush as receiving"
-     " an anwser to a previously tiemed out query."}].
+     " an answer to a previously timed out query."}].
 timeout(Config)  when is_list(Config) ->
 
     {ok, Ref} =  odbc:connect(?RDBMS:connection_string(),
@@ -511,7 +511,7 @@ update_table_timeout(Table, TimeOut, Pid) ->
 
     %% Do not check {updated, 1} as some drivers will return 0
     %% even though the update is done, which is checked by the test
-    %% case when the altered message is recived.
+    %% case when the altered message is received.
     {updated, _} = odbc:sql_query(Ref, UpdateQuery, TimeOut),
 
     ok = odbc:commit(Ref, commit),
@@ -651,7 +651,7 @@ update_table_timeout_reset(Table, TimeOut, Pid) ->
 
     %% Do not check {updated, 1} as some drivers will return 0
     %% even though the update is done, which is checked by the test
-    %% case when the altered message is recived.
+    %% case when the altered message is received.
     {updated, _} = odbc:sql_query(Ref, UpdateQuery, TimeOut),
 
     ok = odbc:commit(Ref, commit),
@@ -836,21 +836,21 @@ api_missuse()->
 api_missuse(Config) when is_list(Config)->
 
     {ok, Ref} =  odbc:connect(?RDBMS:connection_string(), odbc_test_lib:platform_options()),
-    %% Serious programming fault, connetion will be shut down 
+    %% Serious programming fault, connection will be shut down 
     gen_server:call(Ref, {self(), foobar, 10}, infinity),
     ct:sleep(10),
     undefined = process_info(Ref, status),
 
     {ok, Ref2} =  odbc:connect(?RDBMS:connection_string(),
 			       odbc_test_lib:platform_options()),
-    %% Serious programming fault, connetion will be shut down 
+    %% Serious programming fault, connection will be shut down 
     gen_server:cast(Ref2, {self(), foobar, 10}),
     ct:sleep(10),
     undefined = process_info(Ref2, status),
 
     {ok, Ref3} =  odbc:connect(?RDBMS:connection_string(),
 			       odbc_test_lib:platform_options()),
-    %% Could be an innocent misstake the connection lives. 
+    %% Could be an innocent mistake the connection lives. 
     Ref3 ! foobar, 
     ct:sleep(10),
     {status, _} = process_info(Ref3, status).
diff --git a/lib/odbc/test/odbc_data_type_SUITE.erl b/lib/odbc/test/odbc_data_type_SUITE.erl
index a3a4bc78eb..f94550cbe9 100644
--- a/lib/odbc/test/odbc_data_type_SUITE.erl
+++ b/lib/odbc/test/odbc_data_type_SUITE.erl
@@ -1474,7 +1474,7 @@ timestamp(Config) when is_list(Config) ->
     {updated, _} = odbc:param_query(Ref,"INSERT INTO " ++ Table ++  "(FIELD) values(?)",
 				    [{sql_timestamp,Data}]),
     
-    %%% Crate list or database table rows 
+    %%% Create list or database table rows 
     TimeStamps = lists:map(fun(Value) -> {Value} end, Data),
    
     {selected,_, TimeStamps} = odbc:sql_query(Ref, "SELECT * FROM " ++ Table).
diff --git a/lib/odbc/test/odbc_query_SUITE.erl b/lib/odbc/test/odbc_query_SUITE.erl
index c283872965..df8a4641a4 100644
--- a/lib/odbc/test/odbc_query_SUITE.erl
+++ b/lib/odbc/test/odbc_query_SUITE.erl
@@ -531,7 +531,7 @@ duplicate_key(Config) when is_list(Config) ->
 %%-------------------------------------------------------------------------
 not_connection_owner() ->
     [{doc, "Test what happens if a process that did not start the connection"
-	   " tries to acess it."}].
+	   " tries to access it."}].
 not_connection_owner(Config) when is_list(Config) ->
     Ref = proplists:get_value(connection_ref, Config),   
     Table = proplists:get_value(tableName, Config),
@@ -1409,7 +1409,7 @@ describe_string(Config) when is_list(Config) ->
 
 %%-------------------------------------------------------------------------
 describe_floating() ->
-    [{doc,"Test describe_table/[2,3] for floting columns."}].
+    [{doc,"Test describe_table/[2,3] for floating columns."}].
 describe_floating(Config) when is_list(Config) ->
     Ref = proplists:get_value(connection_ref, Config),   
     Table = proplists:get_value(tableName, Config),
diff --git a/lib/odbc/test/oracle.erl b/lib/odbc/test/oracle.erl
index 589401b822..43b1e67f57 100644
--- a/lib/odbc/test/oracle.erl
+++ b/lib/odbc/test/oracle.erl
@@ -85,7 +85,7 @@ multiple_mix()->
 fixed_char_min() ->
     1.
 fixed_char_max() ->
-    2000. %% Should be 255 acording to manual but empirical tests say 2000
+    2000. %% Should be 255 according to manual but empirical tests say 2000
 
 create_fixed_char_table(Size) ->
     " (FIELD char(" ++ integer_to_list(Size) ++ "))".
-- 
2.31.1

openSUSE Build Service is sponsored by