File 0776-Fix-filelib-safe_relative_path-2.patch of Package erlang
From 8e83401d041313907f7c1b94fa6ef294f610d1ef Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Thu, 4 May 2023 15:38:29 +0200
Subject: [PATCH] Fix filelib:safe_relative_path/2
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
The function would return a wrong path if the second argument was a link
and the path in the first argument would descend and then ascend again to
the top level.
The function would also report a path as unsafe by falsely detecting a
link loop if a link would target another link, which in turn would target
a file of the same name like bar --> foo/bar --> (foo/)foo/bar.
Co-authored-by: Björn Gustavsson <bgustavsson@gmail.com>
---
lib/stdlib/src/filelib.erl | 110 +++++++++++++++---------------
lib/stdlib/test/filelib_SUITE.erl | 31 ++++++++-
2 files changed, 85 insertions(+), 56 deletions(-)
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index de08352398..2f0ff53744 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -770,65 +770,65 @@ find_regular_file([File|Files]) ->
Cwd :: filename_all(),
SafeFilename :: filename_all().
+safe_relative_path(Path, "") ->
+ safe_relative_path(Path, ".");
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
+ srp_path(filename:split(Path),
+ Cwd,
+ sets:new([{version, 2}]),
+ []).
+
+srp_path([], _Cwd, _Seen, []) ->
+ "";
+srp_path([], _Cwd, _Seen, Acc) ->
+ filename:join(Acc);
+srp_path(["."|Segs], Cwd, Seen, Acc) ->
+ srp_path(Segs, Cwd, Seen, Acc);
+srp_path([<<".">>|Segs], Cwd, Seen, Acc) ->
+ srp_path(Segs, Cwd, Seen, Acc);
+srp_path([".."|_Segs], _Cwd, _Seen, []) ->
+ unsafe;
+srp_path([".."|Segs], Cwd, Seen, [_|_]=Acc) ->
+ srp_path(Segs, Cwd, Seen, lists:droplast(Acc));
+srp_path([<<"..">>|_Segs], _Cwd, _Seen, []) ->
+ unsafe;
+srp_path([<<"..">>|Segs], Cwd, Seen, [_|_]=Acc) ->
+ srp_path(Segs, Cwd, Seen, lists:droplast(Acc));
+srp_path([clear|Segs], Cwd, _Seen, Acc) ->
+ srp_path(Segs, Cwd, sets:new([{version, 2}]), Acc);
+srp_path([Seg|_]=Segs, Cwd, Seen, Acc) ->
+ case filename:pathtype(Seg) of
relative ->
- Cs0 = filename:split(Path),
- safe_relative_path_1(Cs0, []);
+ srp_segment(Segs, Cwd, Seen, Acc);
_ ->
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)).
+srp_segment([Seg|Segs], Cwd, Seen, Acc) ->
+ Path = filename:join([Cwd|Acc]),
+ case file:read_link(filename:join(Path, Seg)) of
+ {ok, LinkPath} ->
+ srp_link(Path,
+ LinkPath,
+ Segs,
+ Cwd,
+ Seen,
+ Acc);
+ {error, _} ->
+ srp_path(Segs,
+ Cwd,
+ Seen,
+ Acc++[Seg])
+ end.
-climb(_, []) ->
- unsafe;
-climb(T, [_|Acc]) ->
- safe_relative_path_1(T, Acc).
+srp_link(Path, LinkPath, Segs, Cwd, Seen, Acc) ->
+ FullLinkPath = filename:join(Path, LinkPath),
+ case sets:is_element(FullLinkPath, Seen) of
+ true ->
+ unsafe;
+ false ->
+ srp_path(filename:split(LinkPath)++[clear|Segs],
+ Cwd,
+ sets:add_element(FullLinkPath, Seen),
+ Acc)
+ end.
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 179567f128..8b5e9c6377 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -840,7 +840,10 @@ safe_relative_path_links(Config) ->
nested_links_test(BaseDir),
loop_test(BaseDir),
loop_with_parent_test(BaseDir),
- revist_links_test(BaseDir);
+ revist_links_test(BaseDir),
+ descend_climb_cwd_link_test(BaseDir),
+ chained_links_same_target_name_test(BaseDir),
+ ok;
false ->
{skipped, "This platform/user can't create symlinks."}
end
@@ -914,6 +917,32 @@ revist_links_test(BaseDir) ->
"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")).
+descend_climb_cwd_link_test(BaseDir) ->
+ Dir = filename:join(BaseDir, ?FUNCTION_NAME),
+
+ ok = file:make_dir(Dir),
+ ok = file:make_dir(filename:join(Dir, "cwd")),
+
+ ok = file:make_symlink("cwd", filename:join(Dir, "cwd_link")),
+
+ "" = filelib:safe_relative_path("foo/..", filename:join(Dir, "cwd_link")),
+ "bar" = filelib:safe_relative_path("foo/../bar", filename:join(Dir, "cwd_link")),
+ "" = filelib:safe_relative_path("foo/..", filename:join(Dir, "cwd")),
+ "bar" = filelib:safe_relative_path("foo/../bar", filename:join(Dir, "cwd")).
+
+chained_links_same_target_name_test(BaseDir) ->
+ Dir = filename:join(BaseDir, ?FUNCTION_NAME),
+
+ ok = file:make_dir(Dir),
+ ok = file:make_dir(filename:join(Dir, "foo")),
+ ok = file:make_dir(filename:join(Dir, "foo/foo")),
+ ok = file:make_dir(filename:join(Dir, "foo/foo/bar")),
+
+ ok = file:make_symlink("foo/bar", filename:join(Dir, "foo/bar")),
+ ok = file:make_symlink("foo/bar", filename:join(Dir, "bar")),
+
+ "foo/foo/bar" = filelib:safe_relative_path("bar", Dir).
+
rm_rf(Dir) ->
case file:read_link_info(Dir) of
{ok, #file_info{type = directory}} ->
--
2.35.3