File 6311-os_mon-allow-check-intervals-smaller-than-1-minute.patch of Package erlang

From 3fa8a0469773d634f38b514ddd197b4d6a8dbf8c Mon Sep 17 00:00:00 2001
From: jdamanalo <jamanalo5@up.edu.ph>
Date: Thu, 3 Nov 2022 17:54:47 +0800
Subject: [PATCH] os_mon: allow check intervals smaller than 1 minute - expand
 type of `disk_space_check_interval` to `Minute | {TimeUnit, Time}`

---
 lib/os_mon/doc/src/disksup.xml    | 39 ++++++++++++++++++++++++++-----
 lib/os_mon/src/disksup.erl        | 38 +++++++++++++++++++++++-------
 lib/os_mon/test/disksup_SUITE.erl | 39 ++++++++++++++++++++++++++++++-
 3 files changed, 100 insertions(+), 16 deletions(-)

diff --git a/lib/os_mon/doc/src/disksup.xml b/lib/os_mon/doc/src/disksup.xml
index 47eff80ff5..daba73007f 100644
--- a/lib/os_mon/doc/src/disksup.xml
+++ b/lib/os_mon/doc/src/disksup.xml
@@ -57,15 +57,42 @@
       longer valid.</p>
   </description>
 
+  <datatypes>
+    <datatype>
+      <name>time()</name>
+      <desc>
+        <p>Supported units:</p>
+        <taglist>
+          <tag><c>integer() >= 1</c></tag>
+          <item>
+            <p>The time interval in minutes.</p>
+          </item>
+          <tag><c>{TimeUnit, Time}</c></tag>
+          <item>
+            <p>
+              The time interval <c>Time</c> in a time unit specified by <c>TimeUnit</c> where
+              <c>TimeUnit</c> is of the type
+              <seetype marker="erts:erlang#time_unit"><c>erlang:time_unit()</c></seetype>
+              and <c>Time</c> is a positive integer. The time interval needs to be at least one
+              millisecond long.
+            </p>
+          </item>
+        </taglist>
+      </desc>
+    </datatype>
+  </datatypes>
+
   <section>
     <marker id="config"></marker>
     <title>Configuration</title>
     <p>The following configuration parameters can be used to change
       the default values for time interval and threshold:</p>
     <taglist>
-      <tag><c>disk_space_check_interval = int()>0</c></tag>
+      <tag>
+        <c>disk_space_check_interval = </c><seetype marker="#time"><c>time()</c></seetype>
+      </tag>
       <item>
-        <p>The time interval, in minutes, for the periodic disk space
+        <p>The time interval for the periodic disk space
           check. The default is 30 minutes.</p>
       </item>
       <tag><c>disk_almost_full_threshold = float()</c></tag>
@@ -123,13 +150,13 @@
       </desc>
     </func>
     <func>
-      <name since="">set_check_interval(Minutes) -> ok</name>
-      <fsummary>Set time interval, in minutes, for the periodic disk space check</fsummary>
+      <name since="">set_check_interval(Time) -> ok</name>
+      <fsummary>Set time interval for the periodic disk space check</fsummary>
       <type>
-        <v>Minutes = int()>=1</v>
+        <v>Time = <seetype marker="#time">time()</seetype></v>
       </type>
       <desc>
-        <p>Changes the time interval, given in minutes, for the periodic
+        <p>Changes the time interval for the periodic
           disk space check.</p>
         <p>The change will take effect after the next disk space check
           and is non-persist. That is, in case of a process restart,
diff --git a/lib/os_mon/src/disksup.erl b/lib/os_mon/src/disksup.erl
index 80f833bb49..0d824a303d 100644
--- a/lib/os_mon/src/disksup.erl
+++ b/lib/os_mon/src/disksup.erl
@@ -48,12 +48,12 @@ get_disk_data() ->
     os_mon:call(disksup, get_check_interval, infinity).
 
 -spec set_check_interval(time()) -> ok.
-set_check_interval(Minutes) ->
-    case param_type(disk_space_check_interval, Minutes) of
-	true ->
-	    os_mon:call(disksup, {set_check_interval, Minutes}, infinity);
-	false ->
-	    erlang:error(badarg)
+set_check_interval(Value) ->
+    case param_type(disk_space_check_interval, Value) of
+        true ->
+            os_mon:call(disksup, {set_check_interval, Value}, infinity);
+        false ->
+            erlang:error(badarg)
     end.
 
 get_almost_full_threshold() ->
@@ -69,7 +69,12 @@ set_almost_full_threshold(Float) ->
 dummy_reply(get_disk_data) ->
     [{"none", 0, 0}];
 dummy_reply(get_check_interval) ->
-    minutes_to_ms(os_mon:get_env(disksup, disk_space_check_interval));
+    case os_mon:get_env(disksup, disk_space_check_interval) of
+        {TimeUnit, Time} ->
+            erlang:convert_time_unit(Time, TimeUnit, millisecond);
+        Minute ->
+            minutes_to_ms(Minute)
+    end;
 dummy_reply({set_check_interval, _}) ->
     ok;
 dummy_reply(get_almost_full_threshold) ->
@@ -77,6 +82,13 @@ dummy_reply(get_almost_full_threshold) ->
 dummy_reply({set_almost_full_threshold, _}) ->
     ok.
 
+param_type(disk_space_check_interval, {TimeUnit, Time}) ->
+    try erlang:convert_time_unit(Time, TimeUnit, millisecond) of
+        MsTime when MsTime > 0 -> true;
+        _ -> false
+    catch
+        _:_ -> false
+    end;
 param_type(disk_space_check_interval, Val) when is_integer(Val),
 						Val>=1 -> true;
 param_type(disk_almost_full_threshold, Val) when is_number(Val),
@@ -120,20 +132,28 @@ init([]) ->
 
     %% Read the values of some configuration parameters
     Threshold = os_mon:get_env(disksup, disk_almost_full_threshold),
-    Timeout = os_mon:get_env(disksup, disk_space_check_interval),
+    Timeout = case os_mon:get_env(disksup, disk_space_check_interval) of
+                  {TimeUnit, Time} ->
+                      erlang:convert_time_unit(Time, TimeUnit, millisecond);
+                  Minutes ->
+                      minutes_to_ms(Minutes)
+              end,
 
     %% Initiation first disk check
     self() ! timeout,
 
     {ok, #state{port=Port, os=OS,
 		threshold=round(Threshold*100),
-		timeout=minutes_to_ms(Timeout)}}.
+		timeout=Timeout}}.
 
 handle_call(get_disk_data, _From, State) ->
     {reply, State#state.diskdata, State};
 
 handle_call(get_check_interval, _From, State) ->
     {reply, State#state.timeout, State};
+handle_call({set_check_interval, {TimeUnit, Time}}, _From, State) ->
+    Timeout = erlang:convert_time_unit(Time, TimeUnit, millisecond),
+    {reply, ok, State#state{timeout=Timeout}};
 handle_call({set_check_interval, Minutes}, _From, State) ->
     Timeout = minutes_to_ms(Minutes),
     {reply, ok, State#state{timeout=Timeout}};
diff --git a/lib/os_mon/test/disksup_SUITE.erl b/lib/os_mon/test/disksup_SUITE.erl
index a583c1e4d7..1590b1a735 100644
--- a/lib/os_mon/test/disksup_SUITE.erl
+++ b/lib/os_mon/test/disksup_SUITE.erl
@@ -83,6 +83,15 @@ api(Config) when is_list(Config) ->
     1200000 = disksup:get_check_interval(),
     ok = disksup:set_check_interval(30),
 
+    %% set_check_interval({TimeUnit, Time})
+    ok = disksup:set_check_interval({second, 1}),
+    1000 = disksup:get_check_interval(),
+    {'EXIT',{badarg,_}} = (catch disksup:set_check_interval({second, 0.5})),
+    {'EXIT',{badarg,_}} = (catch disksup:set_check_interval({badarg, 1})),
+    {'EXIT',{badarg,_}} = (catch disksup:set_check_interval({nanosecond, 1})),
+    1000 = disksup:get_check_interval(),
+    ok = disksup:set_check_interval(30),
+
     %% get_almost_full_threshold()
     80 = disksup:get_almost_full_threshold(),
 
@@ -110,6 +119,13 @@ config(Config) when is_list(Config) ->
     1740000 = disksup:get_check_interval(),
     81 = disksup:get_almost_full_threshold(),
 
+    ok = application:set_env(os_mon, disk_space_check_interval, {second, 2}),
+
+    ok = supervisor:terminate_child(os_mon_sup, disksup),
+    {ok, _Child2} = supervisor:restart_child(os_mon_sup, disksup),
+
+    2000 = disksup:get_check_interval(),
+
     %% Also try this with bad parameter values, should be ignored
     ok =
 	application:set_env(os_mon, disk_space_check_interval, 0.5),
@@ -117,11 +133,32 @@ config(Config) when is_list(Config) ->
 	application:set_env(os_mon, disk_almost_full_threshold, -0.81),
 
     ok = supervisor:terminate_child(os_mon_sup, disksup),
-    {ok, _Child2} = supervisor:restart_child(os_mon_sup, disksup),
+    {ok, _Child3} = supervisor:restart_child(os_mon_sup, disksup),
 
     1800000 = disksup:get_check_interval(),
     80 = disksup:get_almost_full_threshold(),
 
+    ok = application:set_env(os_mon, disk_space_check_interval, {second, 0.5}),
+
+    ok = supervisor:terminate_child(os_mon_sup, disksup),
+    {ok, _Child4} = supervisor:restart_child(os_mon_sup, disksup),
+
+    1800000 = disksup:get_check_interval(),
+
+    ok = application:set_env(os_mon, disk_space_check_interval, {badarg, 1}),
+
+    ok = supervisor:terminate_child(os_mon_sup, disksup),
+    {ok, _Child5} = supervisor:restart_child(os_mon_sup, disksup),
+
+    1800000 = disksup:get_check_interval(),
+
+    ok = application:set_env(os_mon, disk_space_check_interval, {nanosecond, 1}),
+
+    ok = supervisor:terminate_child(os_mon_sup, disksup),
+    {ok, _Child6} = supervisor:restart_child(os_mon_sup, disksup),
+
+    1800000 = disksup:get_check_interval(),
+
     %% Reset configuration parameters
     ok = application:set_env(os_mon, disk_space_check_interval, 30),
     ok = application:set_env(os_mon, disk_almost_full_threshold, 0.80),
-- 
2.35.3

openSUSE Build Service is sponsored by