File 2721-Add-filelib-safe_relative_path-2.patch of Package erlang

From 3abb4c578df573b17d07d239684758f1b8c93532 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Eric=20Meadows-J=C3=B6nsson?=
 <eric.meadows.jonsson@gmail.com>
Date: Tue, 18 Feb 2020 15:56:20 +0100
Subject: [PATCH 1/3] Add filelib:safe_relative_path/2

Deprecate filename:safe_relative_path/1 in favor of
filelib:safe_relative_path/2.

The filename function does not consider symlinks so it is unsafe to use
on any filesystem that supports symlinks. The new filelib function
follows symlinks and ensures they do not escape the root of the relative
path. It also detects loops in the symlinks to prevent DOS attacks.
---
 lib/stdlib/doc/src/filelib.xml     |  30 +++++++
 lib/stdlib/doc/src/filename.xml    |   4 +
 lib/stdlib/src/filelib.erl         |  69 +++++++++++++++
 lib/stdlib/src/filename.erl        |   1 +
 lib/stdlib/test/filelib_SUITE.erl  | 170 ++++++++++++++++++++++++++++++++++++-
 lib/stdlib/test/filename_SUITE.erl |   2 +-
 6 files changed, 273 insertions(+), 3 deletions(-)

diff --git a/lib/stdlib/doc/src/filelib.xml b/lib/stdlib/doc/src/filelib.xml
index 5df415834f..cb867f8541 100644
--- a/lib/stdlib/doc/src/filelib.xml
+++ b/lib/stdlib/doc/src/filelib.xml
@@ -307,5 +307,35 @@ filelib:wildcard("lib/**/*.{erl,hrl}")</code>
         marker="kernel:kernel_app#source_search_rules"><c>source_search_rules</c></seealso>.</p>
       </desc>
     </func>
+    <func>
+      <name name="safe_relative_path" arity="2" since="OTP 23.0"/>
+      <fsummary>Sanitize a relative path to avoid directory traversal attacks.</fsummary>
+      <desc>
+        <p>Sanitizes the relative path by eliminating ".." and "."
+        components to protect against directory traversal attacks.
+        Either returns the sanitized path name, or the atom
+        <c>unsafe</c> if the path is unsafe.
+        The path is considered unsafe in the following circumstances:</p>
+        <list type="bulleted">
+          <item><p>The path is not relative.</p></item>
+          <item><p>A ".." component would climb up above the root of
+          the relative path.</p></item>
+          <item><p>A symbolic link in the path points above the root
+          of the relative path.</p></item>
+        </list>
+        <p><em>Examples:</em></p>
+        <pre>
+1> <input>{ok, Cwd} = file:get_cwd().</input>
+...
+2> <input>filelib:safe_relative_path("dir/sub_dir/..", Cwd).</input>
+"dir"
+3> <input>filelib:safe_relative_path("dir/..", Cwd).</input>
+[]
+4> <input>filelib:safe_relative_path("dir/../..", Cwd).</input>
+unsafe
+5> <input>filelib:safe_relative_path("/abs/path", Cwd).</input>
+unsafe</pre>
+      </desc>
+    </func>
   </funcs>
 </erlref>
diff --git a/lib/stdlib/doc/src/filename.xml b/lib/stdlib/doc/src/filename.xml
index 60b7eb3436..3dca60c2f0 100644
--- a/lib/stdlib/doc/src/filename.xml
+++ b/lib/stdlib/doc/src/filename.xml
@@ -570,6 +570,10 @@ true
           <item><p>A ".." component would climb up above the root of
           the relative path.</p></item>
         </list>
+        <warning>
+          <p>This function is deprecated. Use <seealso marker="filelib#safe_relative_path/2">
+          <c>filelib:safe_relative_path/2</c></seealso> instead for sanitizing paths.</p>
+        </warning>
         <p><em>Examples:</em></p>
         <pre>
 1> <input>filename:safe_relative_path("dir/sub_dir/..").</input>
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index 239e3828e1..b4c9ffc1b9 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -25,6 +25,7 @@
 -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]).
+-export([safe_relative_path/2]).
 
 %% For debugging/testing.
 -export([compile_wildcard/1]).
@@ -718,3 +719,71 @@ find_regular_file([File|Files]) ->
         true -> {ok, File};
         false -> find_regular_file(Files)
     end.
+
+-spec safe_relative_path(Filename, Cwd) -> unsafe | SafeFilename when
+      Filename :: filename_all(),
+      Cwd :: filename_all(),
+      SafeFilename :: filename_all().
+
+safe_relative_path(Path, Cwd) ->
+    case filename:pathtype(Path) of
+        relative -> safe_relative_path(filename:split(Path), Cwd, [], "");
+        _ -> unsafe
+    end.
+
+safe_relative_path([], _Cwd, _PrevLinks, Acc) ->
+    Acc;
+
+safe_relative_path([Segment | Segments], Cwd, PrevLinks, Acc) ->
+    AccSegment = join(Acc, Segment),
+    case safe_relative_path(AccSegment) of
+        unsafe ->
+            unsafe;
+        SafeAccSegment ->
+            case file:read_link(join(Cwd, SafeAccSegment)) of
+                {ok, LinkPath} ->
+                    case lists:member(LinkPath, PrevLinks) of
+                        true ->
+                            unsafe;
+                        false ->
+                            case safe_relative_path(filename:split(LinkPath), Cwd, [LinkPath | PrevLinks], Acc) of
+                                unsafe -> unsafe;
+                                NewAcc -> safe_relative_path(Segments, Cwd, [], NewAcc)
+                            end
+                    end;
+                {error, _} ->
+                    safe_relative_path(Segments, Cwd, PrevLinks, SafeAccSegment)
+            end
+  end.
+
+join([], Path) -> Path;
+join(Left, Right) -> filename:join(Left, Right).
+
+safe_relative_path(Path) ->
+    case filename:pathtype(Path) of
+        relative ->
+            Cs0 = filename:split(Path),
+            safe_relative_path_1(Cs0, []);
+        _ ->
+            unsafe
+    end.
+
+safe_relative_path_1(["."|T], Acc) ->
+    safe_relative_path_1(T, Acc);
+safe_relative_path_1([<<".">>|T], Acc) ->
+    safe_relative_path_1(T, Acc);
+safe_relative_path_1([".."|T], Acc) ->
+    climb(T, Acc);
+safe_relative_path_1([<<"..">>|T], Acc) ->
+    climb(T, Acc);
+safe_relative_path_1([H|T], Acc) ->
+    safe_relative_path_1(T, [H|Acc]);
+safe_relative_path_1([], []) ->
+    [];
+safe_relative_path_1([], Acc) ->
+    filename:join(lists:reverse(Acc)).
+
+climb(_, []) ->
+    unsafe;
+climb(T, [_|Acc]) ->
+    safe_relative_path_1(T, Acc).
\ No newline at end of file
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl
index f695da6a25..b6df99621f 100644
--- a/lib/stdlib/src/filename.erl
+++ b/lib/stdlib/src/filename.erl
@@ -21,6 +21,7 @@
 
 -deprecated({find_src,1,next_major_release}).
 -deprecated({find_src,2,next_major_release}).
+-deprecated({safe_relative_path,1,next_major_release}).
 
 %% Purpose: Provides generic manipulation of filenames.
 %%
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 527d083eaa..3a1ca9b28a 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -26,7 +26,8 @@
 	 wildcard_one/1,wildcard_two/1,wildcard_errors/1,
 	 fold_files/1,otp_5960/1,ensure_dir_eexist/1,ensure_dir_symlink/1,
 	 wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1,
-         find_source/1, find_source_subdir/1]).
+         find_source/1, find_source_subdir/1, safe_relative_path/1,
+         safe_relative_path_links/1]).
 
 -import(lists, [foreach/2]).
 
@@ -49,7 +50,8 @@ all() ->
     [wildcard_one, wildcard_two, wildcard_errors,
      fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink,
      wildcard_symlink, is_file_symlink, file_props_symlink,
-     find_source, find_source_subdir].
+     find_source, find_source_subdir, safe_relative_path,
+     safe_relative_path_links].
 
 groups() -> 
     [].
@@ -647,3 +649,167 @@ find_source_subdir(Config) when is_list(Config) ->
     {ok, SrcFile} = filelib:find_file(SrcName, BeamDir),
 
     ok.
+
+safe_relative_path(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    Root = filename:join(PrivDir, "filelib_SUITE_safe_relative_path"),
+    ok = file:make_dir(Root),
+    ok = file:set_cwd(Root),
+
+    ok = file:make_dir("a"),
+    ok = file:set_cwd("a"),
+    ok = file:make_dir("b"),
+    ok = file:set_cwd("b"),
+    ok = file:make_dir("c"),
+
+    ok = file:set_cwd(Root),
+
+    "a" = test_srp("a"),
+    "a/b" = test_srp("a/b"),
+    "a/b" = test_srp("a/./b"),
+    "a/b" = test_srp("a/./b/."),
+
+    "" = test_srp("a/.."),
+    "" = test_srp("a/./.."),
+    "" = test_srp("a/../."),
+    "a" = test_srp("a/b/.."),
+    "a" = test_srp("a/../a"),
+    "a" = test_srp("a/../a/../a"),
+    "a/b/c" = test_srp("a/../a/b/c"),
+
+    unsafe = test_srp("a/../.."),
+    unsafe = test_srp("a/../../.."),
+    unsafe = test_srp("a/./../.."),
+    unsafe = test_srp("a/././../../.."),
+    unsafe = test_srp("a/b/././../../.."),
+
+    unsafe = test_srp(PrivDir),                 %Absolute path.
+
+    ok.
+
+test_srp(RelPath) ->
+    Res = do_test_srp(RelPath),
+    Res = case do_test_srp(list_to_binary(RelPath)) of
+              Bin when is_binary(Bin) ->
+                  binary_to_list(Bin);
+              Other ->
+                  Other
+          end.
+
+do_test_srp(RelPath) ->
+    {ok,Root} = file:get_cwd(),
+    ok = file:set_cwd(RelPath),
+    {ok,Cwd} = file:get_cwd(),
+    ok = file:set_cwd(Root),
+    case filelib:safe_relative_path(RelPath, Cwd) of
+        unsafe ->
+            true = length(Cwd) < length(Root),
+            unsafe;
+        "" ->
+            "";
+        SafeRelPath ->
+            ok = file:set_cwd(SafeRelPath),
+            {ok,Cwd} = file:get_cwd(),
+            true = length(Cwd) >= length(Root),
+            ok = file:set_cwd(Root),
+            SafeRelPath
+    end.
+
+safe_relative_path_links(Config) ->
+    PrivDir = ?config(priv_dir, Config),
+    BaseDir = filename:join(PrivDir, "filelib_SUITE_safe_relative_path_links"),
+    ok = file:make_dir(BaseDir),
+    try
+        case check_symlink_support(BaseDir) of
+            true ->
+                simple_test(BaseDir),
+                inside_directory_test(BaseDir),
+                nested_links_test(BaseDir),
+                loop_test(BaseDir),
+                loop_with_parent_test(BaseDir),
+                revist_links_test(BaseDir);
+            false ->
+                {skipped, "This platform/user can't create symlinks."}
+        end
+    after
+        %% This test leaves some rather nasty links that may screw with
+        %% z_SUITE's core file search, so we must make sure everything's
+        %% removed regardless of what happens.
+        rm_rf(BaseDir)
+    end.
+
+check_symlink_support(BaseDir) ->
+    Canary = filename:join(BaseDir, "symlink_canary"),
+    Link = filename:join(BaseDir, "symlink_canary_link"),
+    ok = file:write_file(Canary, <<"chirp">>),
+    ok =:= file:make_symlink(Canary, Link).
+
+simple_test(BaseDir) ->
+    file:make_dir(filename:join(BaseDir, "simple_test")),
+    file:make_symlink("..", filename:join(BaseDir, "simple_test/link")),
+
+    unsafe = filelib:safe_relative_path("link/file", filename:join(BaseDir, "simple_test")),
+    "file" = filelib:safe_relative_path("file", filename:join(BaseDir, "simple_test/link")).
+
+inside_directory_test(BaseDir) ->
+    file:make_dir(filename:join(BaseDir, "inside_directory_test")),
+    file:make_symlink("..", filename:join(BaseDir, "inside_directory_test/link")),
+
+    unsafe = filelib:safe_relative_path("link/file", filename:join(BaseDir, "inside_directory_test")),
+    "file" = filelib:safe_relative_path("file", filename:join(BaseDir, "inside_directory_test/link")).
+
+nested_links_test(BaseDir) ->
+    file:make_dir(filename:join(BaseDir, "nested_links_test")),
+    file:make_dir(filename:join(BaseDir, "nested_links_test/a")),
+    file:make_symlink("a/b/c", filename:join(BaseDir, "nested_links_test/link")),
+    file:make_symlink("..", filename:join(BaseDir, "nested_links_test/a/b")),
+
+    "c/file" = filelib:safe_relative_path("link/file", filename:join(BaseDir, "nested_links_test")),
+
+    file:delete(filename:join(BaseDir, "nested_links_test/a/b")),
+    file:make_symlink("../..", filename:join(BaseDir, "nested_links_test/a/b")),
+    unsafe = filelib:safe_relative_path("link/file", filename:join(BaseDir, "nested_links_test")).
+
+loop_test(BaseDir) ->
+    file:make_dir(filename:join(BaseDir, "loop_test")),
+
+    file:make_symlink("b", filename:join(BaseDir, "loop_test/c")),
+    file:make_symlink("c", filename:join(BaseDir, "loop_test/b")),
+
+    unsafe = filelib:safe_relative_path("c", filename:join(BaseDir, "loop_test")).
+
+loop_with_parent_test(BaseDir) ->
+    file:make_dir(filename:join(BaseDir, "loop_with_parent_test")),
+    file:make_dir(filename:join(BaseDir, "loop_with_parent_test/bar")),
+
+    file:make_symlink("../bar/foo", filename:join(BaseDir, "loop_with_parent_test/bar/foo")),
+
+    unsafe = filelib:safe_relative_path("bar/foo", filename:join(BaseDir, "loop_with_parent_test")).
+
+revist_links_test(BaseDir) ->
+    file:make_dir(filename:join(BaseDir, "revist_links_test")),
+
+    file:make_symlink(".", filename:join(BaseDir, "revist_links_test/x")),
+    file:make_symlink("x", filename:join(BaseDir, "revist_links_test/y")),
+    file:make_symlink("y", filename:join(BaseDir, "revist_links_test/z")),
+
+    "file" = filelib:safe_relative_path("x/file", filename:join(BaseDir, "revist_links_test")),
+    "file" = filelib:safe_relative_path("y/x/file", filename:join(BaseDir, "revist_links_test")),
+    "file" = filelib:safe_relative_path("x/x/file", filename:join(BaseDir, "revist_links_test")),
+    "file" = filelib:safe_relative_path("x/y/x/y/file", filename:join(BaseDir, "revist_links_test")),
+    "file" = filelib:safe_relative_path("x/y/z/x/y/z/file", filename:join(BaseDir, "revist_links_test")),
+    "file" = filelib:safe_relative_path("x/x/y/y/file", filename:join(BaseDir, "revist_links_test")),
+    "file" = filelib:safe_relative_path("x/z/y/x/./z/foo/../x/./y/file", filename:join(BaseDir, "revist_links_test")).
+
+rm_rf(Dir) ->
+    case file:read_link_info(Dir) of
+        {ok, #file_info{type = directory}} ->
+            {ok, Content} = file:list_dir_all(Dir),
+            [ rm_rf(filename:join(Dir,C)) || C <- Content ],
+            file:del_dir(Dir),
+            ok;
+        {ok, #file_info{}} ->
+            file:delete(Dir);
+        _ ->
+            ok
+    end.
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index c977517652..846394d366 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -886,7 +886,7 @@ t_nativename_bin(Config) when is_list(Config) ->
 
 safe_relative_path(Config) ->
     PrivDir = proplists:get_value(priv_dir, Config),
-    Root = filename:join(PrivDir, ?FUNCTION_NAME),
+    Root = filename:join(PrivDir, "filename_SUITE_safe_relative_path"),
     ok = file:make_dir(Root),
     ok = file:set_cwd(Root),
 
-- 
2.16.4

openSUSE Build Service is sponsored by