Skip to content

Commit e453a75

Browse files
authored
Add dereference_symlinks to File.cp* (#12011)
1 parent 5d8d369 commit e453a75

File tree

4 files changed

+178
-54
lines changed

4 files changed

+178
-54
lines changed

lib/elixir/lib/file.ex

Lines changed: 86 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,8 @@ defmodule File do
123123

124124
@type posix_time :: integer()
125125

126+
@type on_conflict_callback :: (Path.t(), Path.t() -> boolean)
127+
126128
@doc """
127129
Returns `true` if the path is a regular file.
128130
@@ -776,11 +778,6 @@ defmodule File do
776778
be a path to a non-existent file. If either is a directory, `{:error, :eisdir}`
777779
will be returned.
778780
779-
The `callback` function is invoked if the `destination_file` already exists.
780-
The function receives arguments for `source_file` and `destination_file`;
781-
it should return `true` if the existing file should be overwritten, `false` if
782-
otherwise. The default callback returns `true`.
783-
784781
The function returns `:ok` in case of success. Otherwise, it returns
785782
`{:error, reason}`.
786783
@@ -792,13 +789,30 @@ defmodule File do
792789
whether the destination is an existing directory or not. We have chosen to
793790
explicitly disallow copying to a destination which is a directory,
794791
and an error will be returned if tried.
792+
793+
## Options
794+
795+
* `:on_conflict` - (since v1.14.0) Invoked when a file already exists in the destination.
796+
The function receives arguments for `source_file` and `destination_file`. It should
797+
return `true` if the existing file should be overwritten, `false` if otherwise.
798+
The default callback returns `true`. On earlier versions, this callback could be
799+
given as third argument, but such behaviour is now deprecated.
800+
795801
"""
796-
@spec cp(Path.t(), Path.t(), (Path.t(), Path.t() -> boolean)) :: :ok | {:error, posix}
797-
def cp(source_file, destination_file, callback \\ fn _, _ -> true end) do
802+
@spec cp(Path.t(), Path.t(), on_conflict: on_conflict_callback) :: :ok | {:error, posix}
803+
def cp(source_file, destination_file, options \\ [])
804+
805+
# TODO: Deprecate me on Elixir v1.19
806+
def cp(source_file, destination_file, callback) when is_function(callback, 2) do
807+
cp(source_file, destination_file, on_conflict: callback)
808+
end
809+
810+
def cp(source_file, destination_file, options) when is_list(options) do
811+
on_conflict = Keyword.get(options, :on_conflict, fn _, _ -> true end)
798812
source_file = IO.chardata_to_string(source_file)
799813
destination_file = IO.chardata_to_string(destination_file)
800814

801-
case do_cp_file(source_file, destination_file, callback, []) do
815+
case do_cp_file(source_file, destination_file, on_conflict, []) do
802816
{:error, reason, _} -> {:error, reason}
803817
_ -> :ok
804818
end
@@ -814,9 +828,9 @@ defmodule File do
814828
The same as `cp/3`, but raises a `File.CopyError` exception if it fails.
815829
Returns `:ok` otherwise.
816830
"""
817-
@spec cp!(Path.t(), Path.t(), (Path.t(), Path.t() -> boolean)) :: :ok
818-
def cp!(source_file, destination_file, callback \\ fn _, _ -> true end) do
819-
case cp(source_file, destination_file, callback) do
831+
@spec cp!(Path.t(), Path.t(), on_conflict: on_conflict_callback) :: :ok
832+
def cp!(source_file, destination_file, options \\ []) do
833+
case cp(source_file, destination_file, options) do
820834
:ok ->
821835
:ok
822836

@@ -839,18 +853,15 @@ defmodule File do
839853
If `source` is a directory, or a symbolic link to it, then `destination` must
840854
be an existent `directory` or a symbolic link to one, or a path to a non-existent directory.
841855
842-
If the source is a file, it copies `source` to
843-
`destination`. If the `source` is a directory, it copies
844-
the contents inside source into the `destination` directory.
856+
If the source is a file, it copies `source` to `destination`. If the `source`
857+
is a directory, it copies the contents inside source into the `destination` directory.
845858
846-
If a file already exists in the destination, it invokes `callback`.
847-
`callback` must be a function that takes two arguments: `source` and `destination`.
848-
The callback should return `true` if the existing file should be overwritten and `false` otherwise.
859+
If a file already exists in the destination, it invokes the optional `on_conflict`
860+
callback given as an option. See "Options" for more information.
849861
850-
This function may fail while copying files,
851-
in such cases, it will leave the destination
852-
directory in a dirty state, where file which have already been copied
853-
won't be removed.
862+
This function may fail while copying files, in such cases, it will leave the
863+
destination directory in a dirty state, where file which have already been
864+
copied won't be removed.
854865
855866
The function returns `{:ok, files_and_directories}` in case of
856867
success, `files_and_directories` lists all files and directories copied in no
@@ -861,6 +872,19 @@ defmodule File do
861872
explicitly disallow this behaviour. If `source` is a `file` and `destination`
862873
is a directory, `{:error, :eisdir}` will be returned.
863874
875+
## Options
876+
877+
* `:on_conflict` - (since v1.14.0) Invoked when a file already exists in the destination.
878+
The function receives arguments for `source` and `destination`. It should return
879+
`true` if the existing file should be overwritten, `false` if otherwise. The default
880+
callback returns `true`. On earlier versions, this callback could be given as third
881+
argument, but such behaviour is now deprecated.
882+
883+
* `:dereference_symlinks` - (since v1.14.0) By default, this function will copy symlinks
884+
by creating symlinks that point to the same location. This option forces symlinks to be
885+
dereferenced and have their contents copied instead when set to `true`. If the dereferenced
886+
files do not exist, than the operation fails. The default is `false`.
887+
864888
## Examples
865889
866890
# Copies file "a.txt" to "b.txt"
@@ -870,14 +894,28 @@ defmodule File do
870894
File.cp_r("samples", "tmp")
871895
872896
# Same as before, but asks the user how to proceed in case of conflicts
873-
File.cp_r("samples", "tmp", fn source, destination ->
897+
File.cp_r("samples", "tmp", on_conflict: fn source, destination ->
874898
IO.gets("Overwriting #{destination} by #{source}. Type y to confirm. ") == "y\n"
875899
end)
876900
877901
"""
878-
@spec cp_r(Path.t(), Path.t(), (Path.t(), Path.t() -> boolean)) ::
902+
@spec cp_r(Path.t(), Path.t(),
903+
on_conflict: on_conflict_callback,
904+
dereference_symlinks: boolean()
905+
) ::
879906
{:ok, [binary]} | {:error, posix, binary}
880-
def cp_r(source, destination, callback \\ fn _, _ -> true end) when is_function(callback, 2) do
907+
908+
def cp_r(source, destination, options \\ [])
909+
910+
# TODO: Deprecate me on Elixir v1.19
911+
def cp_r(source, destination, callback) when is_function(callback, 2) do
912+
cp_r(source, destination, on_conflict: callback)
913+
end
914+
915+
def cp_r(source, destination, options) when is_list(options) do
916+
on_conflict = Keyword.get(options, :on_conflict, fn _, _ -> true end)
917+
dereference? = Keyword.get(options, :dereference_symlinks, false)
918+
881919
source =
882920
source
883921
|> IO.chardata_to_string()
@@ -888,7 +926,7 @@ defmodule File do
888926
|> IO.chardata_to_string()
889927
|> assert_no_null_byte!("File.cp_r/3")
890928

891-
case do_cp_r(source, destination, callback, []) do
929+
case do_cp_r(source, destination, on_conflict, dereference?, []) do
892930
{:error, _, _} = error -> error
893931
res -> {:ok, res}
894932
end
@@ -898,9 +936,12 @@ defmodule File do
898936
The same as `cp_r/3`, but raises a `File.CopyError` exception if it fails.
899937
Returns the list of copied files otherwise.
900938
"""
901-
@spec cp_r!(Path.t(), Path.t(), (Path.t(), Path.t() -> boolean)) :: [binary]
902-
def cp_r!(source, destination, callback \\ fn _, _ -> true end) do
903-
case cp_r(source, destination, callback) do
939+
@spec cp_r!(Path.t(), Path.t(),
940+
on_conflict: on_conflict_callback,
941+
dereference_symlinks: boolean()
942+
) :: [binary]
943+
def cp_r!(source, destination, options \\ []) do
944+
case cp_r(source, destination, options) do
904945
{:ok, files} ->
905946
files
906947

@@ -914,15 +955,21 @@ defmodule File do
914955
end
915956
end
916957

917-
defp do_cp_r(src, dest, callback, acc) when is_list(acc) do
958+
defp do_cp_r(src, dest, on_conflict, dereference?, acc) when is_list(acc) do
918959
case :elixir_utils.read_link_type(src) do
919960
{:ok, :regular} ->
920-
do_cp_file(src, dest, callback, acc)
961+
do_cp_file(src, dest, on_conflict, acc)
921962

922963
{:ok, :symlink} ->
923964
case :file.read_link(src) do
924-
{:ok, link} -> do_cp_link(link, src, dest, callback, acc)
925-
{:error, reason} -> {:error, reason, src}
965+
{:ok, link} when dereference? ->
966+
do_cp_r(Path.expand(link, Path.dirname(src)), dest, on_conflict, dereference?, acc)
967+
968+
{:ok, link} ->
969+
do_cp_link(link, src, dest, on_conflict, acc)
970+
971+
{:error, reason} ->
972+
{:error, reason, src}
926973
end
927974

928975
{:ok, :directory} ->
@@ -931,7 +978,7 @@ defmodule File do
931978
case mkdir(dest) do
932979
success when success in [:ok, {:error, :eexist}] ->
933980
Enum.reduce(files, [dest | acc], fn x, acc ->
934-
do_cp_r(Path.join(src, x), Path.join(dest, x), callback, acc)
981+
do_cp_r(Path.join(src, x), Path.join(dest, x), on_conflict, dereference?, acc)
935982
end)
936983

937984
{:error, reason} ->
@@ -950,9 +997,8 @@ defmodule File do
950997
end
951998
end
952999

953-
# If we reach this clause, there was an error while
954-
# processing a file.
955-
defp do_cp_r(_, _, _, acc) do
1000+
# If we reach this clause, there was an error while processing a file.
1001+
defp do_cp_r(_, _, _, _, acc) do
9561002
acc
9571003
end
9581004

@@ -961,14 +1007,14 @@ defmodule File do
9611007
end
9621008

9631009
# Both src and dest are files.
964-
defp do_cp_file(src, dest, callback, acc) do
1010+
defp do_cp_file(src, dest, on_conflict, acc) do
9651011
case :file.copy(src, {dest, [:exclusive]}) do
9661012
{:ok, _} ->
9671013
copy_file_mode!(src, dest)
9681014
[dest | acc]
9691015

9701016
{:error, :eexist} ->
971-
if path_differs?(src, dest) and callback.(src, dest) do
1017+
if path_differs?(src, dest) and on_conflict.(src, dest) do
9721018
case copy(src, dest) do
9731019
{:ok, _} ->
9741020
copy_file_mode!(src, dest)
@@ -987,13 +1033,13 @@ defmodule File do
9871033
end
9881034

9891035
# Both src and dest are files.
990-
defp do_cp_link(link, src, dest, callback, acc) do
1036+
defp do_cp_link(link, src, dest, on_conflict, acc) do
9911037
case :file.make_symlink(link, dest) do
9921038
:ok ->
9931039
[dest | acc]
9941040

9951041
{:error, :eexist} ->
996-
if path_differs?(src, dest) and callback.(src, dest) do
1042+
if path_differs?(src, dest) and on_conflict.(src, dest) do
9971043
# If rm/1 fails, :file.make_symlink/2 will fail
9981044
_ = rm(dest)
9991045

lib/elixir/test/elixir/file_test.exs

Lines changed: 82 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -470,7 +470,7 @@ defmodule FileTest do
470470
end
471471
end
472472

473-
test "copy file to itself" do
473+
test "cp itself" do
474474
src = dest = tmp_path("tmp.file")
475475

476476
File.write!(src, "here")
@@ -592,6 +592,86 @@ defmodule FileTest do
592592
assert File.cp_r(src, dest) == {:error, :enoent, src}
593593
end
594594

595+
test "cp_r with absolute symlink" do
596+
linked_src = fixture_path("cp_r")
597+
src = tmp_path("tmp/src")
598+
dest = tmp_path("tmp/dest")
599+
600+
File.mkdir_p!(src)
601+
:ok = :file.make_symlink(Path.join(linked_src, "a"), Path.join(src, "sym"))
602+
603+
try do
604+
{:ok, files} = File.cp_r(src, dest)
605+
assert length(files) == 2
606+
607+
assert File.exists?(tmp_path("tmp/dest/sym/1.txt"))
608+
assert File.exists?(tmp_path("tmp/dest/sym/a/2.txt"))
609+
after
610+
File.rm_rf(src)
611+
File.rm_rf(dest)
612+
end
613+
end
614+
615+
test "cp_r with dereference absolute symlink" do
616+
linked_src = fixture_path("cp_r")
617+
src = tmp_path("tmp/src")
618+
dest = tmp_path("tmp/dest")
619+
620+
File.mkdir_p!(src)
621+
:ok = :file.make_symlink(Path.join(linked_src, "a"), Path.join(src, "sym"))
622+
623+
try do
624+
{:ok, files} = File.cp_r(src, dest, dereference_symlinks: true)
625+
assert length(files) == 5
626+
627+
assert File.exists?(tmp_path("tmp/dest/sym/1.txt"))
628+
assert File.exists?(tmp_path("tmp/dest/sym/a/2.txt"))
629+
after
630+
File.rm_rf(src)
631+
File.rm_rf(dest)
632+
end
633+
end
634+
635+
@tag :unix
636+
test "cp_r with relative symlink" do
637+
doc = tmp_path("tmp/doc")
638+
src = tmp_path("tmp/src")
639+
dest = tmp_path("tmp/dest")
640+
641+
File.mkdir_p!(src)
642+
File.write!(doc, "hello")
643+
:ok = :file.make_symlink("../doc", Path.join(src, "sym"))
644+
645+
try do
646+
{:ok, files} = File.cp_r(src, dest)
647+
assert length(files) == 2
648+
assert File.lstat!(tmp_path("tmp/dest/sym")).type == :symlink
649+
after
650+
File.rm_rf(src)
651+
File.rm_rf(dest)
652+
end
653+
end
654+
655+
@tag :unix
656+
test "cp_r with dereference relative symlink" do
657+
doc = tmp_path("tmp/doc")
658+
src = tmp_path("tmp/src")
659+
dest = tmp_path("tmp/dest")
660+
661+
File.mkdir_p!(src)
662+
File.write!(doc, "hello")
663+
:ok = :file.make_symlink("../doc", Path.join(src, "sym"))
664+
665+
try do
666+
{:ok, files} = File.cp_r(src, dest, dereference_symlinks: true)
667+
assert length(files) == 2
668+
assert File.lstat!(tmp_path("tmp/dest/sym")).type == :regular
669+
after
670+
File.rm_rf(src)
671+
File.rm_rf(dest)
672+
end
673+
end
674+
595675
test "cp_r with dir and file conflict" do
596676
src = fixture_path("cp_r")
597677
dest = tmp_path("tmp")
@@ -687,7 +767,7 @@ defmodule FileTest do
687767
end
688768
end
689769

690-
test "cp_r with src_unknown!" do
770+
test "cp_r! with src unknown" do
691771
src = fixture_path("unknown")
692772
dest = tmp_path("tmp")
693773

lib/mix/lib/mix/release.ex

Lines changed: 1 addition & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -823,14 +823,7 @@ defmodule Mix.Release do
823823
for dir <- @copy_app_dirs do
824824
source_dir = Path.join(source_app, dir)
825825
target_dir = Path.join(target_app, dir)
826-
827-
source_dir =
828-
case File.read_link(source_dir) do
829-
{:ok, link_target} -> Path.expand(link_target, source_app)
830-
_ -> source_dir
831-
end
832-
833-
File.exists?(source_dir) && File.cp_r!(source_dir, target_dir)
826+
File.exists?(source_dir) && File.cp_r!(source_dir, target_dir, dereference_symlinks: true)
834827
end
835828

836829
true

0 commit comments

Comments
 (0)