File 4771-Add-filelib-ensure_path-1.patch of Package erlang

From 3b095254d663145ecdb63a3db6cb291c7b0fabfb Mon Sep 17 00:00:00 2001
From: Bryan Paxton <bryan@starbelly.io>
Date: Tue, 18 Jan 2022 08:48:40 -0600
Subject: [PATCH] Add filelib:ensure_path/1

---
 lib/stdlib/doc/src/filelib.xml    | 17 +++++++
 lib/stdlib/src/filelib.erl        | 53 ++++++++++++---------
 lib/stdlib/test/filelib_SUITE.erl | 76 +++++++++++++++++++++++++++++++
 3 files changed, 125 insertions(+), 21 deletions(-)

diff --git a/lib/stdlib/doc/src/filelib.xml b/lib/stdlib/doc/src/filelib.xml
index 815eb23931..082bec358b 100644
--- a/lib/stdlib/doc/src/filelib.xml
+++ b/lib/stdlib/doc/src/filelib.xml
@@ -107,6 +107,23 @@
       </desc>
     </func>
 
+    <func>
+      <name name="ensure_path" arity="1" since=""/>
+      <fsummary>Ensure that all parent directories for a target directory exist.</fsummary>
+      <desc>
+        <p>Ensures that all parent directories for the specified path
+        <c><anno>Path</anno></c> exist, trying to create them if
+        necessary.</p>
+	<p>Unlike <seemfa
+	marker="#ensure_dir/1"><c>ensure_dir/1</c></seemfa>, this
+	function will attempt to create all path segments as a
+	directory, including the last segment.</p>
+        <p>Returns <c>ok</c> if all parent directories already exist
+        or can be created. Returns <c>{error, <anno>Reason</anno>}</c> if
+        some parent directory does not exist and cannot be created.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="file_size" arity="1" since=""/>
       <fsummary>Return the size in bytes of a file.</fsummary>
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index 74e7bfc9cc..de08352398 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -21,7 +21,7 @@
 
 %% File utilities.
 -export([wildcard/1, wildcard/2, is_dir/1, is_file/1, is_regular/1]).
--export([fold_files/5, last_modified/1, file_size/1, ensure_dir/1]).
+-export([fold_files/5, last_modified/1, file_size/1, ensure_dir/1, ensure_path/1]).
 -export([wildcard/3, is_dir/2, is_file/2, is_regular/2]).
 -export([fold_files/6, last_modified/2, file_size/2]).
 -export([find_file/2, find_file/3, find_source/1, find_source/2, find_source/3]).
@@ -218,6 +218,7 @@ do_file_size(File, Mod) ->
 	    0
     end.
 
+
 %%----------------------------------------------------------------------
 %% +type ensure_dir(X) -> ok | {error, Reason}.
 %% +type X = filename() | dirname()
@@ -230,27 +231,37 @@ ensure_dir("/") ->
     ok;
 ensure_dir(F) ->
     Dir = filename:dirname(F),
-    case do_is_dir(Dir, file) of
-	true ->
-	    ok;
-	false when Dir =:= F ->
-	    %% Protect against infinite loop
-	    {error,einval};
-	false ->
-	    _ = ensure_dir(Dir),
-	    case file:make_dir(Dir) of
-		{error,eexist}=EExist ->
-		    case do_is_dir(Dir, file) of
-			true ->
-			    ok;
-			false ->
-			    EExist
-		    end;
-		Err ->
-		    Err
-	    end
-    end.
+    ensure_path(Dir).
 
+-spec ensure_path(Path) -> 'ok' | {'error', Reason} when
+      Path :: dirname_all(),
+      Reason :: file:posix().
+ensure_path("/") ->
+    ok;
+
+ensure_path(Path) -> 
+    case do_is_dir(Path, file) of
+        true -> 
+            ok;
+        false -> 
+            case filename:dirname(Path) of 
+                Parent when Parent =:= Path -> 
+                    {error,einval};
+                Parent -> 
+                     _ = ensure_path(Parent),
+                    case file:make_dir(Path) of
+                        {error,eexist}=EExist ->
+                            case do_is_dir(Path, file) of
+                                true -> 
+                                    ok;
+                                false -> 
+                                    EExist 
+                            end;
+                        Other ->
+                            Other
+                    end
+            end
+    end.
 
 %%%
 %%% Pattern matching using a compiled wildcard.
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 0db8f4f329..eac0dea4d8 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -25,6 +25,10 @@
 	 init_per_testcase/2,end_per_testcase/2,
 	 wildcard_one/1,wildcard_two/1,wildcard_errors/1,
 	 fold_files/1,otp_5960/1,ensure_dir_eexist/1,ensure_dir_symlink/1,
+         ensure_path_single_dir/1, ensure_path_nested_dirs/1,
+         ensure_path_binary_args/1, ensure_path_symlink/1,
+         ensure_path_relative_path/1, ensure_path_relative_path_dot_dot/1,
+         ensure_path_invalid_path/1,
 	 wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1,
          find_source/1, find_source_subdir/1, safe_relative_path/1,
          safe_relative_path_links/1]).
@@ -49,6 +53,10 @@ suite() ->
 all() -> 
     [wildcard_one, wildcard_two, wildcard_errors,
      fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink,
+     ensure_path_single_dir, ensure_path_nested_dirs, ensure_path_binary_args,
+     ensure_path_symlink, ensure_path_relative_path,
+     ensure_path_relative_path_dot_dot,
+     ensure_path_invalid_path,
      wildcard_symlink, is_file_symlink, file_props_symlink,
      find_source, find_source_subdir, safe_relative_path,
      safe_relative_path_links].
@@ -458,6 +466,74 @@ ensure_dir_symlink(Config) when is_list(Config) ->
             ok = filelib:ensure_dir(SymlinkedName)
     end.
 
+ensure_path_single_dir(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    Dir = filename:join(PrivDir, "ensure_path_single_dir"),
+    ok = filelib:ensure_path(Dir),
+    true = filelib:is_dir(Dir).
+
+ensure_path_nested_dirs(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    BaseDir = filename:join(PrivDir, "ensure_path_nested_dirs"),
+    Path = filename:join(BaseDir, "foo/bar/baz"),
+    ok = filelib:ensure_path(Path),
+    true = filelib:is_dir(Path).
+
+ensure_path_binary_args(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    BaseDir = filename:join(PrivDir, "ensure_path_binary_args"),
+    Path = filename:join(BaseDir, "foo/bar/baz"),
+    ok = filelib:ensure_path(list_to_binary(Path)),
+    true = filelib:is_dir(Path).
+
+ensure_path_invalid_path(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    BaseDir = filename:join(PrivDir, "ensure_path_invalid_path"),
+    ok = filelib:ensure_path(BaseDir),
+    FileName =  filename:join(BaseDir, "foo"),
+    ok = file:write_file(FileName, <<"eh?\n">>),
+    Path = filename:join(FileName, "foo/bar/baz"),
+    {error,enotdir} = filelib:ensure_path(Path),
+    false = filelib:is_dir(Path).
+
+ensure_path_relative_path(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    BaseDir = filename:join(PrivDir, "ensure_path_relative_path"),
+    ok = filelib:ensure_path(BaseDir),
+    ok = file:set_cwd(BaseDir),
+    Path = filename:join(BaseDir, "foo/bar/baz"),
+    ok = filelib:ensure_path("foo/bar/baz"),
+    true = filelib:is_dir(Path).
+
+ensure_path_relative_path_dot_dot(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    BaseDir = filename:join(PrivDir, "ensure_path_relative_path"),
+    SubDir = filename:join(BaseDir, "dot_dot"),
+    ok = filelib:ensure_path(SubDir),
+    ok = file:set_cwd(SubDir),
+    Path = filename:join(BaseDir, "foo/bar/baz"),
+    ok = filelib:ensure_path("../foo/bar/baz"),
+    true = filelib:is_dir(Path).
+
+ensure_path_symlink(Config) when is_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    Dir = filename:join(PrivDir, "ensure_path_symlink"),
+    Name = filename:join(Dir, "same_name_as_file_and_dir"),
+    ok = filelib:ensure_path(Dir),
+    ok = file:write_file(Name, <<"some string\n">>),
+    %% With a symlink to the directory.
+    Symlink = filename:join(PrivDir, "ensure_path_symlink_link"),
+    case file:make_symlink(Dir, Symlink) of
+        {error,enotsup} ->
+            {skip,"Symlinks not supported on this platform"};
+        {error,eperm} ->
+            {win32,_} = os:type(),
+            {skip,"Windows user not privileged to create symlinks"};
+        ok ->
+            SymlinkedName = filename:join(Symlink, "same_name_as_file_and_dir"),
+            ok = filelib:ensure_dir(SymlinkedName)
+    end.
+
 wildcard_symlink(Config) when is_list(Config) ->
     PrivDir = proplists:get_value(priv_dir, Config),
     Dir = filename:join(PrivDir, ?MODULE_STRING++"_wildcard_symlink"),
-- 
2.34.1

openSUSE Build Service is sponsored by