Skip to content

Commit

Permalink
fix: Support prefixes other than a/ & b/ when modifying files (#1…
Browse files Browse the repository at this point in the history
…0899)

Signed-off-by: Marek Kubica <marek@tarides.com>
  • Loading branch information
Leonidas-from-XIV authored Sep 10, 2024
1 parent 2498355 commit 9b805a0
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 9 deletions.
5 changes: 4 additions & 1 deletion src/dune_patch/dune_patch.ml
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,10 @@ let patches_of_string patch_string =
( Path.Local.split_first_component old_path
, Path.Local.split_first_component new_path )
with
| Some ("a", _old_path), Some ("b", new_path) -> new_path, 1
| Some (_, old_path), Some (_, new_path)
when Path.Local.equal old_path new_path && not (Path.Local.is_root new_path) ->
(* suffixes are the same and not empty *)
new_path, 1
| _, _ -> new_path, 0
in
(* Replace file *)
Expand Down
11 changes: 3 additions & 8 deletions test/expect-tests/dune_patch/dune_patch_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -239,14 +239,9 @@ let%expect_test "patching a file without prefix" =
;;

let%expect_test "patching files with freestyle prefix" =
try
test [ "foo.ml", "This is wrong\n" ] ("foo.patch", random_prefix);
check "foo.ml";
[%expect.unreachable]
with
| Dune_util.Report_error.Already_reported ->
print_endline @@ normalize_error_path [%expect.output];
[%expect {| Error: foo.ml: No such file or directory |}]
test [ "foo.ml", "This is wrong\n" ] ("foo.patch", random_prefix);
check "foo.ml";
[%expect {| This is right |}]
;;

let%expect_test "patching files with spaces" =
Expand Down

0 comments on commit 9b805a0

Please sign in to comment.