File 3671-Simplify-some-calls-to-application-get_env-2.patch of Package erlang

From 4452b205dfdba1c7632da02fc42364eccecd7ed2 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 16 Jan 2023 13:08:23 +0100
Subject: [PATCH] Simplify some calls to application:get_env/2

Replace some calls to `application:get_env/2` with
`application:get_env/3`. This simplifies the code at the call site,
and as an additional benefit, `application:get_env/3` is slightly more
efficient than `application:get_env/2`.
---
 lib/kernel/src/error_logger.erl  | 10 ++++------
 lib/kernel/src/group_history.erl |  5 +----
 lib/stdlib/src/shell.erl         | 34 +++++++++++---------------------
 3 files changed, 17 insertions(+), 32 deletions(-)

diff --git a/lib/kernel/src/error_logger.erl b/lib/kernel/src/error_logger.erl
index 74dc524988..66b42dfc82 100644
--- a/lib/kernel/src/error_logger.erl
+++ b/lib/kernel/src/error_logger.erl
@@ -578,11 +578,9 @@ limit_term(Term) ->
 -spec get_format_depth() -> 'unlimited' | pos_integer().
 
 get_format_depth() ->
-    case application:get_env(kernel, error_logger_format_depth) of
-	{ok, Depth} when is_integer(Depth) ->
+    case application:get_env(kernel, error_logger_format_depth, unlimited) of
+	Depth when is_integer(Depth) ->
 	    max(10, Depth);
-        {ok, unlimited} ->
-            unlimited;
-	undefined ->
-	    unlimited
+        unlimited ->
+            unlimited
     end.
diff --git a/lib/kernel/src/group_history.erl b/lib/kernel/src/group_history.erl
index aae4748139..46648fba85 100644
--- a/lib/kernel/src/group_history.erl
+++ b/lib/kernel/src/group_history.erl
@@ -310,10 +310,7 @@ disk_log_info(Tag) ->
     Value.
 
 find_wrap_values() ->
-    ConfSize = case application:get_env(kernel, shell_history_file_bytes) of
-        undefined -> ?DEFAULT_SIZE;
-        {ok, S} -> S
-    end,
+    ConfSize = application:get_env(kernel, shell_history_file_bytes, ?DEFAULT_SIZE),
     SizePerFile = max(?MIN_HISTORY_SIZE, ConfSize div ?MAX_HISTORY_FILES),
     FileCount = if SizePerFile > ?MIN_HISTORY_SIZE ->
                        ?MAX_HISTORY_FILES
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index c8610b23ee..5301f57222 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -399,15 +399,13 @@ prompt(N, Eval0, Bs0, RT, FT, Ds0) ->
     end.
 
 get_prompt_func() ->
-    case application:get_env(stdlib, shell_prompt_func) of
-        {ok,{M,F}=PromptFunc} when is_atom(M), is_atom(F) ->
+    case application:get_env(stdlib, shell_prompt_func, default) of
+        {M,F}=PromptFunc when is_atom(M), is_atom(F) ->
             PromptFunc;
-        {ok,default=Default} ->
+        default=Default ->
             Default;
-        {ok,Term} ->
+        Term ->
             bad_prompt_func(Term),
-            default;
-        undefined ->
             default
     end.
 
@@ -763,8 +761,8 @@ do_catch(exit, restricted_shell_stopped) ->
 do_catch(exit, restricted_shell_started) ->
     false;
 do_catch(_Class, _Reason) ->
-    case application:get_env(stdlib, shell_catch_exception) of
-        {ok, true} ->
+    case application:get_env(stdlib, shell_catch_exception, false) of
+        true ->
             true;
         _ ->
             false
@@ -1609,13 +1607,7 @@ pp(V, I, RT) ->
     pp(V, I, _Depth=?LINEMAX, RT).
 
 pp(V, I, D, RT) ->
-    Strings =
-        case application:get_env(stdlib, shell_strings) of
-            {ok, false} ->
-                false;
-            _ ->
-                true
-        end,
+    Strings = application:get_env(stdlib, shell_strings, true) =/= false,
     io_lib_pretty:print(V, ([{column, I}, {line_length, columns()},
                              {depth, D}, {line_max_chars, ?CHAR_MAX},
                              {strings, Strings},
@@ -1475,26 +1475,24 @@ garb(Shell) ->
     erlang:garbage_collect().
 
 get_env(V, Def) ->
-    case application:get_env(stdlib, V) of
-	{ok, Val} when is_integer(Val), Val >= 0 ->
-	    Val;
-	_ ->
-	    Def
+    case application:get_env(stdlib, V, Def) of
+        Val when is_integer(Val), Val >= 0 ->
+            Val;
+        _ ->
+            Def
     end.
-	    
+
 check_env(V) ->
-    case application:get_env(stdlib, V) of
-	undefined ->
-	    ok;
-	{ok, Val} when is_integer(Val), Val >= 0 ->
-	    ok;
-        {ok, Val} ->
+    case application:get_env(stdlib, V, 0) of
+        Val when is_integer(Val), Val >= 0 ->
+            ok;
+        Val ->
             Txt = io_lib:fwrite
                     ("Invalid value of STDLIB configuration parameter"
                      "~tw: ~tp\n", [V, Val]),
-	    error_logger:info_report(lists:flatten(Txt))
+            error_logger:info_report(lists:flatten(Txt))
     end.
-	    
+
 set_env(App, Name, Val, Default) ->
     Prev = case application:get_env(App, Name) of
 	       undefined ->
-- 
2.35.3

openSUSE Build Service is sponsored by