File 0796-Fix-typos-in-lib-observer.patch of Package erlang

From 87416dcae7437d1bba8fdf0a2d6bd79dd193c396 Mon Sep 17 00:00:00 2001
From: "Kian-Meng, Ang" <kianmeng@cpan.org>
Date: Wed, 22 Dec 2021 16:04:03 +0800
Subject: [PATCH] Fix typos in lib/observer

---
 lib/observer/doc/src/observer_ug.xml         | 6 +++---
 lib/observer/doc/src/ttb_ug.xml              | 2 +-
 lib/observer/src/cdv_proc_cb.erl             | 2 +-
 lib/observer/src/crashdump_viewer.erl        | 4 ++--
 lib/observer/src/crashdump_viewer.hrl        | 2 +-
 lib/observer/src/etop.erl                    | 2 +-
 lib/observer/src/observer_procinfo.erl       | 2 +-
 lib/observer/src/observer_trace_wx.erl       | 6 +++---
 lib/observer/src/observer_wx.erl             | 4 ++--
 lib/observer/src/ttb.erl                     | 2 +-
 lib/observer/src/ttb_et.erl                  | 2 +-
 lib/observer/test/crashdump_viewer_SUITE.erl | 2 +-
 lib/observer/test/ttb_SUITE.erl              | 2 +-
 13 files changed, 19 insertions(+), 19 deletions(-)

diff --git a/lib/observer/doc/src/observer_ug.xml b/lib/observer/doc/src/observer_ug.xml
index b0e8ef5872..348e613c85 100644
--- a/lib/observer/doc/src/observer_ug.xml
+++ b/lib/observer/doc/src/observer_ug.xml
@@ -314,7 +314,7 @@
     <title>Table Viewer Tab</title>
     <p>Tab <em>Table Viewer</em> lists tables. By default, ETS tables
     are displayed whereas unreadable private ETS tables and tables created by OTP
-    applications are not diplayed. Use menu <em>View</em> to view "system"
+    applications are not displayed. Use menu <em>View</em> to view "system"
     ETS tables, unreadable ETS tables, or Mnesia tables.
     </p>
     <p>Double-click to view the table content, or right-click and
@@ -360,7 +360,7 @@
       the <em>Ports</em> tab.  A special <em>new</em> identifier,
       meaning all processes, or ports, started after trace start, can
       be added with buttons <em>Add 'new' Processes</em> and <em>Add
-      'new' Ports</em>, respecively.
+      'new' Ports</em>, respectively.
     </p>
     <p>
       When adding processes or ports, a window with trace options is
diff --git a/lib/observer/doc/src/ttb_ug.xml b/lib/observer/doc/src/ttb_ug.xml
index be24db1aac..0411694c4e 100644
--- a/lib/observer/doc/src/ttb_ug.xml
+++ b/lib/observer/doc/src/ttb_ug.xml
@@ -394,7 +394,7 @@ check(stop) ->
 	    this way is then merged with all other traces.</p>
           <p>The autostart feature requires more data to be stored on
             traced nodes. By default, the data is stored automatically
-            to the file named "ttb_autostart.bin" in the currect working directory
+            to the file named "ttb_autostart.bin" in the current working directory
 	    (cwd) of the traced node.
             Users can change this behaviour (that is, on diskless
             nodes) by specifying their own module to handle autostart data
diff --git a/lib/observer/src/cdv_proc_cb.erl b/lib/observer/src/cdv_proc_cb.erl
index aee817a097..f5b78643c0 100644
--- a/lib/observer/src/cdv_proc_cb.erl
+++ b/lib/observer/src/cdv_proc_cb.erl
@@ -153,7 +153,7 @@ info_fields() ->
        {"Old Binary vheap", old_bin_vheap},
        {"Binary vheap unused",  bin_vheap_unused},
        {"Old Binary vheap unused", old_bin_vheap_unused},
-       {"Number of Heap Fragements", num_heap_frag},
+       {"Number of Heap Fragments", num_heap_frag},
        {"Heap Fragment Data",heap_frag_data},
        {"New Heap Start",   new_heap_start},
        {"New Heap Top",     new_heap_top},
diff --git a/lib/observer/src/crashdump_viewer.erl b/lib/observer/src/crashdump_viewer.erl
index 71df6fd4b0..6de837da93 100644
--- a/lib/observer/src/crashdump_viewer.erl
+++ b/lib/observer/src/crashdump_viewer.erl
@@ -1651,7 +1651,7 @@ read_heap_lines_1(Fd, Acc) ->
 
             %% Reduce the memory consumption by converting the
             %% line to a binary. Measurements show that it may also
-            %% be benefical for performance, too, because it makes the
+            %% be beneficial for performance, too, because it makes the
             %% garbage collections cheaper.
 
             Line = list_to_binary(Line1),
@@ -3356,7 +3356,7 @@ collect(Pids,Acc) ->
 	    collect(lists:delete(Pid,Pids),[Result|Acc]);
         {'DOWN', _Ref, process, Pid, _Error} ->
             Warning =
-                "WARNING: an error occured while parsing data.\n" ++
+                "WARNING: an error occurred while parsing data.\n" ++
                 case get(truncated) of
                     true -> "This might be because the dump is truncated.\n";
                     false -> ""
diff --git a/lib/observer/src/crashdump_viewer.hrl b/lib/observer/src/crashdump_viewer.hrl
index 856e558e6c..d84935a570 100644
--- a/lib/observer/src/crashdump_viewer.hrl
+++ b/lib/observer/src/crashdump_viewer.hrl
@@ -42,7 +42,7 @@
 	}).
 
 -record(proc,
-	%% Initial data according to the follwoing:
+	%% Initial data according to the following:
 	%% 
 	%% msg_q_len, reds, memory and stack_heap are integers because it must
 	%% be possible to sort on them. All other fields are strings
diff --git a/lib/observer/src/etop.erl b/lib/observer/src/etop.erl
index f0990f1f25..901320204e 100644
--- a/lib/observer/src/etop.erl
+++ b/lib/observer/src/etop.erl
@@ -38,7 +38,7 @@ help() ->
       "Options are:~n"
       "  node        atom       Required   The erlang node to measure ~n"
       "  port        integer    The used port, NOTE: due to a bug this program~n"
-      "                         will hang if the port is not avaiable~n"
+      "                         will hang if the port is not available~n"
       "  accumulate  boolean    If true execution time is accumulated ~n"
       "  lines       integer    Number of displayed processes~n"
       "  interval    integer    Display update interval in secs~n"
diff --git a/lib/observer/src/observer_procinfo.erl b/lib/observer/src/observer_procinfo.erl
index 7ffdba262a..a22f76a4c7 100644
--- a/lib/observer/src/observer_procinfo.erl
+++ b/lib/observer/src/observer_procinfo.erl
@@ -339,7 +339,7 @@ fetch_state_info2(Pid, M) ->
 	    %% Formatted status ?
 	    case lists:keyfind(format_status, 1, rpc:call(node(Pid), M, module_info, [exports])) of
 		false	-> Opt = {"Format", unknown};
-		_	-> Opt = {"Format", overriden}
+		_	-> Opt = {"Format", overridden}
 	    end,
 	    [{"Behaviour", B}, Opt, {"State",OtherFormat}];
 	{badrpc,{'EXIT',{timeout, _}}} -> []
diff --git a/lib/observer/src/observer_trace_wx.erl b/lib/observer/src/observer_trace_wx.erl
index 5b8d4f5568..5b4e98a909 100644
--- a/lib/observer/src/observer_trace_wx.erl
+++ b/lib/observer/src/observer_trace_wx.erl
@@ -361,7 +361,7 @@ handle_event(#wx{event = #wxCommand{type = command_togglebutton_clicked, command
 	(TProcs == []) andalso (TPorts == []) andalso throw({error, "No processes or ports traced"}),
 	(Nodes == []) andalso throw({error, "No nodes traced"}),
 	HaveCallTrace = fun(#titem{opts=Os}) -> lists:member(functions,Os) end,
-	WStr = "Call trace actived but no trace patterns used",
+	WStr = "Call trace activated but no trace patterns used",
 	(TPs == []) andalso lists:any(HaveCallTrace, TProcs) andalso
 	    observer_wx:create_txt_dialog(Panel, WStr, "Warning", ?wxICON_WARNING),
 
@@ -763,7 +763,7 @@ do_add_patterns({Module, NewPs}, State=#state{tpatterns=TPs0, m_view=Mview, f_vi
 	{Old, [], []} ->
 	    State;
 	{MPatterns, _New, _Changed} ->
-	    %% if dynamicly updates update New and Changed
+	    %% if dynamically updates update New and Changed
 	    TPs = dict:store(Module, MPatterns, TPs0),
 	    update_modules_view(lists:sort(dict:fetch_keys(TPs)), Module, Mview),
 	    update_functions_view(dict:fetch(Module, TPs), Fview),
@@ -1048,7 +1048,7 @@ textformat(Trace) when element(1, Trace) == trace_ts, tuple_size(Trace) >= 4 ->
 textformat(Trace) when element(1, Trace) == drop, tuple_size(Trace) =:= 2 ->
     io_lib:format("*** Dropped ~p messages.~n", [element(2,Trace)]);
 textformat(Trace) when element(1, Trace) == seq_trace, tuple_size(Trace) >= 3 ->
-    io_lib:format("*** Seq trace not implmented.~n", []);
+    io_lib:format("*** Seq trace not implemented.~n", []);
 textformat(_) ->
     "".
 
diff --git a/lib/observer/src/observer_wx.erl b/lib/observer/src/observer_wx.erl
index 22243aa3e1..0fc76bcfa2 100644
--- a/lib/observer/src/observer_wx.erl
+++ b/lib/observer/src/observer_wx.erl
@@ -559,7 +559,7 @@ try_rpc(Node, Mod, Func, Args) ->
 return_to_localnode(Frame, Node) ->
     case node() =/= Node of
 	true ->
-	    create_txt_dialog(Frame, "Error occured on remote node",
+	    create_txt_dialog(Frame, "Error occurred on remote node",
 			      "Error", ?wxICON_ERROR),
 	    disconnect_node(Node);
 	false ->
@@ -836,7 +836,7 @@ is_rb_compatible(Node) ->
 
 is_rb_server_running(Node, LogState) ->
    %% If already started, somebody else may use it.
-   %% We cannot use it too, as far log file would be overriden. Not fair.
+   %% We cannot use it too, as far log file would be overridden. Not fair.
    case rpc:block_call(Node, erlang, whereis, [rb_server]) of
        Pid when is_pid(Pid), (LogState == false) ->
 	   throw("Error: rb_server is already started and maybe used by someone.");
diff --git a/lib/observer/src/ttb.erl b/lib/observer/src/ttb.erl
index 29a572d7fe..168fbd7729 100644
--- a/lib/observer/src/ttb.erl
+++ b/lib/observer/src/ttb.erl
@@ -1199,7 +1199,7 @@ start_client(FileOrWrap,Traci) ->
 		     {fun handler/2, dict:to_list(Traci)}).
 
 handler(Trace,Traci) ->
-    %%We return our own Traci so that it not necesarry to look it up
+    %%We return our own Traci so that it not necessary to look it up
     %%This may take time if something huge has been written to it
     receive
 	{get,Collector} -> Collector ! {self(),{Trace,Traci}};
diff --git a/lib/observer/src/ttb_et.erl b/lib/observer/src/ttb_et.erl
index f90a7f6dcf..b8d8d42560 100644
--- a/lib/observer/src/ttb_et.erl
+++ b/lib/observer/src/ttb_et.erl
@@ -52,7 +52,7 @@ collector(Trace) ->
 %% all events backwards and collect call/return information:
 %%
 %% MFA collected from return_to events is added to call and
-%% return_from events as {caller,MFA} and {return_to,MFA} respecively.
+%% return_from events as {caller,MFA} and {return_to,MFA} respectively.
 %% MFA collected from call events is added to return_to events as
 %% {return_from,MFA}
 %%
diff --git a/lib/observer/test/ttb_SUITE.erl b/lib/observer/test/ttb_SUITE.erl
index ab02cdabb4..c9378501d4 100644
--- a/lib/observer/test/ttb_SUITE.erl
+++ b/lib/observer/test/ttb_SUITE.erl
@@ -876,7 +876,7 @@ flush(Acc) ->
     end.
 
 foo() ->
-    %% Sync between nodes is not always exact, so here is a litle timeout to 
+    %% Sync between nodes is not always exact, so here is a little timeout to 
     %% make sure traces come i correct sequence when merging.
     %% In the real world there is no way to avoid this kind of trouble
     timer:sleep(100),
-- 
2.31.1

openSUSE Build Service is sponsored by