Skip to content

Commit 3b5d4e8

Browse files
authored
refactor: get rid of [Stdune.Path] (#1402)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent b0f6330 commit 3b5d4e8

File tree

6 files changed

+4
-10
lines changed

6 files changed

+4
-10
lines changed

ocaml-lsp-server/src/bin.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,4 +5,4 @@ let _PATH =
55
lazy (Bin.parse_path (Option.value ~default:"" (Unix_env.get Unix_env.initial "PATH")))
66
;;
77

8-
let which = Bin.which ~path:(Lazy.force _PATH)
8+
let which x = Bin.which ~path:(Lazy.force _PATH) x |> Option.map ~f:Stdune.Path.to_string

ocaml-lsp-server/src/bin.mli

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1 @@
1-
open Import
2-
3-
val which : string -> Fpath.t option
1+
val which : string -> string option

ocaml-lsp-server/src/import.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@ include struct
66
module Code_error = Code_error
77
module Comparable = Comparable
88
module Exn_with_backtrace = Exn_with_backtrace
9-
module Fpath = Path
109
module Int = Int
1110
module Table = Table
1211
module Tuple = Tuple

ocaml-lsp-server/src/merlin_config.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,6 @@ module Process = struct
6969
~message:"dune binary not found"
7070
())
7171
| Some prog ->
72-
let prog = Fpath.to_string prog in
7372
let stdin_r, stdin_w = Unix.pipe () in
7473
let stdout_r, stdout_w = Unix.pipe () in
7574
Unix.set_close_on_exec stdin_w;

ocaml-lsp-server/src/ocamlformat.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -136,8 +136,7 @@ let formatter doc =
136136
| `Other -> Code_error.raise "unable to format non merlin document" []))
137137
;;
138138

139-
let exec cancel bin args stdin =
140-
let refmt = Fpath.to_string bin in
139+
let exec cancel refmt args stdin =
141140
let+ res, cancel = run_command cancel refmt stdin args in
142141
match cancel with
143142
| Cancelled () ->

ocaml-lsp-server/src/ocamlformat_rpc.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ module Process : sig
2424

2525
val create
2626
: logger:(type_:MessageType.t -> message:string -> unit Fiber.t)
27-
-> bin:Fpath.t
27+
-> bin:string
2828
-> unit
2929
-> (t, [> `No_process ]) result Fiber.t
3030

@@ -62,7 +62,6 @@ end = struct
6262
;;
6363

6464
let create ~logger ~bin () =
65-
let bin = Fpath.to_string bin in
6665
let* pid, stdout, stdin =
6766
let stdin_i, stdin_o = Unix.pipe ~cloexec:true () in
6867
let stdout_i, stdout_o = Unix.pipe ~cloexec:true () in

0 commit comments

Comments
 (0)