File 7416-os_mon-Add-specs-to-all-documented-functions.patch of Package erlang
From 7d7d14cae47cd8076fcd64cf2b18f588e3c35531 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Thu, 4 Jan 2024 21:35:29 +0100
Subject: [PATCH 6/6] os_mon: Add specs to all documented functions
---
lib/os_mon/doc/src/disksup.xml | 4 ++--
lib/os_mon/src/disksup.erl | 20 ++++++++++++++++++++
lib/os_mon/src/memsup.erl | 19 +++++++++++++++++++
lib/os_mon/src/nteventlog.erl | 15 +++++++++++++++
lib/os_mon/src/os_sup.erl | 12 ++++++++++++
5 files changed, 68 insertions(+), 2 deletions(-)
diff --git a/lib/os_mon/doc/src/disksup.xml b/lib/os_mon/doc/src/disksup.xml
index 97872c9f3b..dd1165fa39 100644
--- a/lib/os_mon/doc/src/disksup.xml
+++ b/lib/os_mon/doc/src/disksup.xml
@@ -222,8 +222,8 @@
<v>Float = float(), 0=<Float=<1</v>
</type>
<desc>
- <p>Changes the threshold, given as a float, for disk space
- utilization.</p>
+ <p>Changes the threshold, given as a float (0.0 =< Float =< 1.0),
+ for disk space utilization.</p>
<p>The change will take effect during the next disk space check
and is non-persist. That is, in case of a process restart,
this value is forgotten and the default value will be used.
diff --git a/lib/os_mon/src/disksup.erl b/lib/os_mon/src/disksup.erl
index 714c29b589..144dbb6ee7 100644
--- a/lib/os_mon/src/disksup.erl
+++ b/lib/os_mon/src/disksup.erl
@@ -45,15 +45,33 @@
start_link() ->
gen_server:start_link({local, disksup}, disksup, [], []).
+-spec get_disk_data() -> [DiskData] when
+ DiskData :: {Id, TotalKiB, Capacity},
+ Id :: string(),
+ TotalKiB :: integer(),
+ Capacity :: integer().
get_disk_data() ->
os_mon:call(disksup, get_disk_data, infinity).
+-spec get_disk_info() -> [DiskData] when
+ DiskData :: {Id, TotalKiB, AvailableKiB, Capacity},
+ Id :: string(),
+ TotalKiB :: integer(),
+ AvailableKiB :: integer(),
+ Capacity :: integer().
get_disk_info() ->
os_mon:call(disksup, get_disk_info, infinity).
+-spec get_disk_info(Path :: string()) -> [DiskData] when
+ DiskData :: {Id, TotalKiB, AvailableKiB, Capacity},
+ Id :: string(),
+ TotalKiB :: integer(),
+ AvailableKiB :: integer(),
+ Capacity :: integer().
get_disk_info(Path) ->
os_mon:call(disksup, {get_disk_info, Path}, infinity).
+-spec get_check_interval() -> Milliseconds :: integer().
get_check_interval() ->
os_mon:call(disksup, get_check_interval, infinity).
@@ -66,8 +84,10 @@ set_check_interval(Value) ->
erlang:error(badarg)
end.
+-spec get_almost_full_threshold() -> Percent :: integer().
get_almost_full_threshold() ->
os_mon:call(disksup, get_almost_full_threshold, infinity).
+-spec set_almost_full_threshold(Float :: float()) -> ok.
set_almost_full_threshold(Float) ->
case param_type(disk_almost_full_threshold, Float) of
true ->
diff --git a/lib/os_mon/src/memsup.erl b/lib/os_mon/src/memsup.erl
index c467adc2e5..a0e58ec797 100644
--- a/lib/os_mon/src/memsup.erl
+++ b/lib/os_mon/src/memsup.erl
@@ -68,17 +68,30 @@
start_link() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
+-spec get_os_wordsize() -> Wordsize when Wordsize :: 32 | 64 | unsupported_os.
get_os_wordsize() ->
os_mon:call(memsup, get_os_wordsize, infinity).
+-spec get_memory_data() -> {Total, Allocated, Worst} when
+ Total :: integer(),
+ Allocated :: integer(),
+ Worst :: {Pid, PidAllocated} | undefined,
+ Pid :: pid(),
+ PidAllocated :: integer().
get_memory_data() ->
os_mon:call(memsup, get_memory_data, infinity).
+-spec get_system_memory_data() -> MemDataList when
+ MemDataList :: [{Tag, Size}],
+ Tag :: atom(),
+ Size :: integer().
get_system_memory_data() ->
os_mon:call(memsup, get_system_memory_data, infinity).
+-spec get_check_interval() -> Milliseconds :: integer().
get_check_interval() ->
os_mon:call(memsup, get_check_interval, infinity).
+-spec set_check_interval(Minutes :: non_neg_integer()) -> ok.
set_check_interval(Minutes) ->
case param_type(memory_check_interval, Minutes) of
true ->
@@ -88,8 +101,10 @@ set_check_interval(Minutes) ->
erlang:error(badarg)
end.
+-spec get_procmem_high_watermark() -> integer().
get_procmem_high_watermark() ->
os_mon:call(memsup, get_procmem_high_watermark, infinity).
+-spec set_procmem_high_watermark(Float :: term()) -> ok.
set_procmem_high_watermark(Float) ->
case param_type(process_memory_high_watermark, Float) of
true ->
@@ -99,8 +114,10 @@ set_procmem_high_watermark(Float) ->
erlang:error(badarg)
end.
+-spec get_sysmem_high_watermark() -> integer().
get_sysmem_high_watermark() ->
os_mon:call(memsup, get_sysmem_high_watermark, infinity).
+-spec set_sysmem_high_watermark(Float :: term()) -> ok.
set_sysmem_high_watermark(Float) ->
case param_type(system_memory_high_watermark, Float) of
true ->
@@ -110,8 +127,10 @@ set_sysmem_high_watermark(Float) ->
erlang:error(badarg)
end.
+-spec get_helper_timeout() -> Seconds :: integer().
get_helper_timeout() ->
os_mon:call(memsup, get_helper_timeout, infinity).
+-spec set_helper_timeout(Seconds :: non_neg_integer()) -> ok.
set_helper_timeout(Seconds) ->
case param_type(memsup_helper_timeout, Seconds) of
true ->
diff --git a/lib/os_mon/src/nteventlog.erl b/lib/os_mon/src/nteventlog.erl
index ff3d57415a..0a48b56f85 100644
--- a/lib/os_mon/src/nteventlog.erl
+++ b/lib/os_mon/src/nteventlog.erl
@@ -33,13 +33,28 @@
%% API
%%----------------------------------------------------------------------
+-spec start_link(Identifier, MFA) -> Result when Identifier :: string() | atom(),
+ MFA :: {Mod, Func, Args},
+ Mod :: atom(),
+ Func :: atom(),
+ Args :: [term()],
+ Result :: {ok, Pid} | {error, {already_started, Pid}},
+ Pid :: pid().
start_link(Ident, MFA) ->
gen_server:start_link({local, nteventlog}, nteventlog,
[Ident, MFA], []).
+-spec start(Identifier, MFA) -> Result when Identifier :: string() | atom(),
+ MFA :: {Mod, Func, Args},
+ Mod :: atom(),
+ Func :: atom(),
+ Args :: [term()],
+ Result :: {ok, Pid} | {error, {already_started, Pid}},
+ Pid :: pid().
start(Ident, MFA) ->
gen_server:start({local, nteventlog}, nteventlog, [Ident, MFA], []).
+-spec stop() -> stopped.
stop() ->
gen_server:call(nteventlog, stop).
diff --git a/lib/os_mon/src/os_sup.erl b/lib/os_mon/src/os_sup.erl
index f983e8bac2..de87e0a670 100644
--- a/lib/os_mon/src/os_sup.erl
+++ b/lib/os_mon/src/os_sup.erl
@@ -53,13 +53,25 @@ stop() ->
error_report(LogData, Tag) ->
error_logger:error_report(Tag, LogData).
+-spec enable() -> ok | {error, Res} when
+ Res :: string().
enable() ->
command(enable).
+-spec enable(Dir, Conf) -> ok | {error, Res} when
+ Dir :: string(),
+ Conf :: string(),
+ Res :: string().
enable(Path, Conf) ->
command(enable, Path, Conf).
+-spec disable() -> ok | {error, Res} when
+ Res :: string().
disable() ->
command(disable).
+-spec disable(Dir, Conf) -> ok | {error, Res} when
+ Dir :: string(),
+ Conf :: string(),
+ Res :: string().
disable(Path, Conf) ->
command(disable, Path, Conf).
--
2.35.3