Skip to content

Commit

Permalink
refactor(path): remove dead code (#7180)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Feb 26, 2023
1 parent 6fa1a17 commit 89d73f2
Show file tree
Hide file tree
Showing 3 changed files with 0 additions and 41 deletions.
10 changes: 0 additions & 10 deletions otherlibs/stdune/src/path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1129,16 +1129,6 @@ let extend_basename t ~suffix =
| In_build_dir t -> in_build_dir (Local.extend_basename t ~suffix)
| External t -> external_ (External.extend_basename t ~suffix)

let insert_after_build_dir_exn =
let error a b =
Code_error.raise "Path.insert_after_build_dir_exn"
[ ("path", to_dyn a); ("insert", String b) ]
in
fun a b ->
match a with
| In_build_dir a -> in_build_dir (Local.append (Local.of_string b) a)
| In_source_tree _ | External _ -> error a b

let clear_dir dir = Fpath.clear_dir (to_string dir)

let rm_rf ?(allow_external = false) t =
Expand Down
2 changes: 0 additions & 2 deletions otherlibs/stdune/src/path.mli
Original file line number Diff line number Diff line change
Expand Up @@ -352,8 +352,6 @@ val is_strict_descendant_of_build_dir : t -> bool
(** Split after the first component if [t] is local *)
val split_first_component : t -> (Filename.t * t) option

val insert_after_build_dir_exn : t -> string -> t

val exists : t -> bool

val readdir_unsorted :
Expand Down
29 changes: 0 additions & 29 deletions otherlibs/stdune/test/path_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,6 @@ let reach_for_running p ~from =

let relative p s = Path.to_dyn (Path.relative p s) |> print_dyn

let insert_after_build_dir_exn p s =
Path.insert_after_build_dir_exn p s |> Path.to_dyn |> print_dyn

let append_source x y = Path.append_source x y |> Path.to_dyn |> print_dyn

let drop_build_context p =
Expand Down Expand Up @@ -292,26 +289,6 @@ let%expect_test _ =
false
|}]

let%expect_test _ =
insert_after_build_dir_exn Path.root "foobar";
[%expect.unreachable]
[@@expect.uncaught_exn
{|
( "(\"Path.insert_after_build_dir_exn\",\
\n{ path = In_source_tree \".\"; insert = \"foobar\" })") |}]

let%expect_test _ =
insert_after_build_dir_exn Path.build_dir "foobar";
[%expect {|
In_build_dir "foobar"
|}]

let%expect_test _ =
insert_after_build_dir_exn (Path.relative Path.build_dir "qux") "foobar";
[%expect {|
In_build_dir "foobar/qux"
|}]

let%expect_test _ =
append_source Path.build_dir (Path.Source.relative Path.Source.root "foo");
[%expect {|
Expand Down Expand Up @@ -423,12 +400,6 @@ let%expect_test _ =
"c/d"
|}]

let%expect_test _ =
local_part (Path.insert_after_build_dir_exn Path.build_dir "c/d");
[%expect {|
"c/d"
|}]

let%expect_test _ =
local_part (r "c/d");
[%expect {|
Expand Down

0 comments on commit 89d73f2

Please sign in to comment.