File 0180-Disksup-parsing-for-df-output-on-POSIX-and-SUSv3-sys.patch of Package erlang

From ae49fdda74a72f9fea596dba4f0470163f28d4b5 Mon Sep 17 00:00:00 2001
From: Dmytro Lytovchenko <dmytro.lytovchenko@gmail.com>
Date: Tue, 4 Jul 2017 15:21:26 +0200
Subject: [PATCH] Disksup parsing for 'df' output on POSIX and SUSv3 systems
 Tests for disksup:parse_df

---
 lib/os_mon/src/disksup.erl        | 98 +++++++++++++++++++++++++++++++++++++--
 lib/os_mon/test/disksup_SUITE.erl | 38 ++++++++++++++-
 2 files changed, 129 insertions(+), 7 deletions(-)

diff --git a/lib/os_mon/src/disksup.erl b/lib/os_mon/src/disksup.erl
index 492e4814d..36730aac7 100644
--- a/lib/os_mon/src/disksup.erl
+++ b/lib/os_mon/src/disksup.erl
@@ -32,7 +32,7 @@
 	 terminate/2, code_change/3]).
 
 %% Other exports
--export([format_status/2]).
+-export([format_status/2, parse_df/2]).
 
 -record(state, {threshold, timeout, os, diskdata = [],port}).
 
@@ -294,8 +294,8 @@ check_disks_solaris("", _Threshold) ->
 check_disks_solaris("\n", _Threshold) ->
     [];
 check_disks_solaris(Str, Threshold) ->
-    case io_lib:fread("~s~d~d~d~d%~s", Str) of
-	{ok, [_FS, KB, _Used, _Avail, Cap, MntOn], RestStr} ->
+    case parse_df(Str, posix) of
+	{ok, {KB, Cap, MntOn}, RestStr} ->
 	    if
 		Cap >= Threshold ->
 		    set_alarm({disk_almost_full, MntOn}, []);
@@ -308,14 +308,102 @@ check_disks_solaris(Str, Threshold) ->
 	    check_disks_solaris(skip_to_eol(Str),Threshold)
     end.
 
+%% @private
+%% @doc Predicate to take a word from the input string until a space or
+%% a percent '%' sign (the Capacity field is followed by a %)
+parse_df_is_not_space($ ) -> false;
+parse_df_is_not_space($%) -> false;
+parse_df_is_not_space(_) -> true.
+
+%% @private
+%% @doc Predicate to take spaces away from string. Stops on a non-space
+parse_df_is_space($ ) -> true;
+parse_df_is_space(_) -> false.
+
+%% @private
+%% @doc Predicate to consume remaining characters until end of line.
+parse_df_is_not_eol($\r) -> false;
+parse_df_is_not_eol($\n) -> false;
+parse_df_is_not_eol(_)   -> true.
+
+%% @private
+%% @doc Trims leading non-spaces (the word) from the string then trims spaces.
+parse_df_skip_word(Input) ->
+    Remaining = lists:dropwhile(fun parse_df_is_not_space/1, Input),
+    lists:dropwhile(fun parse_df_is_space/1, Remaining).
+
+%% @private
+%% @doc Takes all non-spaces and then drops following spaces.
+parse_df_take_word(Input) ->
+    {Word, Remaining0} = lists:splitwith(fun parse_df_is_not_space/1, Input),
+    Remaining1 = lists:dropwhile(fun parse_df_is_space/1, Remaining0),
+    {Word, Remaining1}.
+
+%% @private
+%% @doc Takes all non-spaces and then drops the % after it and the spaces.
+parse_df_take_word_percent(Input) ->
+    {Word, Remaining0} = lists:splitwith(fun parse_df_is_not_space/1, Input),
+    %% Drop the leading % or do nothing
+    Remaining1 = case Remaining0 of
+                     [$% | R1] -> R1;
+                     _ -> Remaining0 % Might be no % or empty list even
+                 end,
+    Remaining2 = lists:dropwhile(fun parse_df_is_space/1, Remaining1),
+    {Word, Remaining2}.
+
+%% @private
+%% @doc Given a line of 'df' POSIX/SUSv3 output split it into fields:
+%% a string (mounted device), 4 integers (kilobytes, used, available
+%% and capacity), skip % sign, (optionally for susv3 can also skip IUsed, IFree
+%% and ICap% fields) then take remaining characters as the mount path
+-spec parse_df(string(), posix | susv3) ->
+    {error, parse_df} | {ok, {integer(), integer(), integer()}, string()}.
+parse_df(Input0, Flavor) ->
+    %% Format of Posix/Linux df output looks like Header + Lines
+    %% Filesystem     1024-blocks     Used Available Capacity Mounted on
+    %% udev               2467108        0   2467108       0% /dev
+    Input1 = parse_df_skip_word(Input0), % skip device path field
+    {KbStr, Input2} = parse_df_take_word(Input1), % take Kb field
+    Input3 = parse_df_skip_word(Input2), % skip Used field
+    Input4 = parse_df_skip_word(Input3), % skip Avail field
+
+    % take Capacity% field; drop a % sign following the capacity
+    {CapacityStr, Input5} = parse_df_take_word_percent(Input4),
+
+    %% Format of OS X/SUSv3 df looks similar to POSIX but has 3 extra columns
+    %% Filesystem 1024-blocks Used Available Capacity iused ifree %iused Mounted
+    %% /dev/disk1   243949060 2380  86690680    65% 2029724 37555    0%  /
+    Input6 = case Flavor of
+                 posix -> Input5;
+                 susv3 -> % there are 3 extra integers we want to skip
+                     Input5a = parse_df_skip_word(Input5), % skip IUsed field
+                     Input5b = parse_df_skip_word(Input5a), % skip IFree field
+                     %% skip the value of ICap + '%' field
+                     {_, Input5c} = parse_df_take_word_percent(Input5b),
+                     Input5c
+             end,
+
+    % path is the remaining string till end of line
+    {MountPath, Input7} = lists:splitwith(fun parse_df_is_not_eol/1, Input6),
+    % Trim the newlines
+    Remaining = lists:dropwhile(fun(X) -> not parse_df_is_not_eol(X) end,
+                                Input7),
+    try
+        Kb = erlang:list_to_integer(KbStr),
+        Capacity = erlang:list_to_integer(CapacityStr),
+        {ok, {Kb, Capacity, MountPath}, Remaining}
+    catch error:badarg ->
+        {error, parse_df}
+    end.
+
 % Parse per SUSv3 specification, notably recent OS X
 check_disks_susv3("", _Threshold) ->
     [];
 check_disks_susv3("\n", _Threshold) ->
     [];
 check_disks_susv3(Str, Threshold) ->
-    case io_lib:fread("~s~d~d~d~d%~d~d~d%~s", Str) of
-    {ok, [_FS, KB, _Used, _Avail, Cap, _IUsed, _IFree, _ICap, MntOn], RestStr} ->
+    case parse_df(Str, susv3) of
+    {ok, {KB, Cap, MntOn}, RestStr} ->
 	    if
 		Cap >= Threshold ->
 		    set_alarm({disk_almost_full, MntOn}, []);
diff --git a/lib/os_mon/test/disksup_SUITE.erl b/lib/os_mon/test/disksup_SUITE.erl
index ad6198501..d7f262616 100644
--- a/lib/os_mon/test/disksup_SUITE.erl
+++ b/lib/os_mon/test/disksup_SUITE.erl
@@ -30,7 +30,7 @@
 -export([port/1]).
 -export([terminate/1, unavailable/1, restart/1]).
 -export([otp_5910/1]).
--export([posix_only/1]).
+-export([posix_only/1, parse_df_output_posix/1, parse_df_output_susv3/1]).
 
 init_per_suite(Config) when is_list(Config) ->
     ok = application:start(os_mon),
@@ -59,7 +59,8 @@ suite() ->
 
 all() -> 
     Bugs = [otp_5910],
-    Always = [api, config, alarm, port, posix_only, unavailable] ++ Bugs,
+    Always = [api, config, alarm, port, posix_only, unavailable,
+              parse_df_output_posix, parse_df_output_susv3] ++ Bugs,
     case test_server:os_type() of
 	{unix, _OSname} -> Always;
 	{win32, _OSname} -> Always;
@@ -413,3 +414,36 @@ get_disk_data([{"none",0,0}=E]) -> [E];
 get_disk_data([{_,_,0}|Es]) -> get_disk_data(Es);
 get_disk_data([E|Es]) -> [E|get_disk_data(Es)];
 get_disk_data([]) -> [].
+
+%% @doc Test various expected inputs to 'df' command output (Linux/POSIX)
+parse_df_output_posix(Config) when is_list(Config) ->
+    PosixHdr = "Filesystem     1K-blocks     Used Available Use% Mounted on\n",
+    {error, _} = disksup:parse_df(PosixHdr, posix),
+    {error, _} = disksup:parse_df("", posix),
+    {error, _} = disksup:parse_df("\n\n", posix),
+
+    %% Have a simple example with no funny spaces in mount path
+    Posix1 = "tmpfs             498048     7288    490760   2% /run\n",
+    {ok, {498048, 2, "/run"}, ""} = disksup:parse_df(Posix1, posix),
+
+    %% Have a mount path with some spaces in it
+    Posix2 = "tmpfs             498048     7288    490760   2% /spaces 1 2\n",
+    {ok, {498048, 2, "/spaces 1 2"}, ""} = disksup:parse_df(Posix2, posix).
+
+%% @doc Test various expected inputs to 'df' command output (Darwin/SUSv3)
+parse_df_output_susv3(Config) when is_list(Config) ->
+    DarwinHdr = "Filesystem 1024-blocks      Used Available Capacity " ++
+                "iused      ifree %iused  Mounted on",
+    {error, _} = disksup:parse_df(DarwinHdr, susv3),
+    {error, _} = disksup:parse_df("", susv3),
+    {error, _} = disksup:parse_df("\n\n", susv3),
+
+    %% Have a simple example with no funny spaces in mount path
+    Darwin1 = "/dev/disk1   243949060 157002380  86690680    65% 2029724 " ++
+              "4292937555    0%   /\n",
+    {ok, {243949060, 65, "/"}, ""} = disksup:parse_df(Darwin1, susv3),
+
+    %% Have a mount path with some spaces in it
+    Darwin2 = "/dev/disk1   243949060 157002380  86690680    65% 2029724 " ++
+              "4292937555    0%   /spaces 1 2\n",
+    {ok, {243949060, 65, "/spaces 1 2"}, ""} = disksup:parse_df(Darwin2, susv3).
-- 
2.13.3

openSUSE Build Service is sponsored by