Skip to content

Commit

Permalink
refactor: get rid of [Stdune.Path] (#1402)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Nov 21, 2024
1 parent b0f6330 commit 3b5d4e8
Show file tree
Hide file tree
Showing 6 changed files with 4 additions and 10 deletions.
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/bin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,4 +5,4 @@ let _PATH =
lazy (Bin.parse_path (Option.value ~default:"" (Unix_env.get Unix_env.initial "PATH")))
;;

let which = Bin.which ~path:(Lazy.force _PATH)
let which x = Bin.which ~path:(Lazy.force _PATH) x |> Option.map ~f:Stdune.Path.to_string
4 changes: 1 addition & 3 deletions ocaml-lsp-server/src/bin.mli
Original file line number Diff line number Diff line change
@@ -1,3 +1 @@
open Import

val which : string -> Fpath.t option
val which : string -> string option
1 change: 0 additions & 1 deletion ocaml-lsp-server/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ include struct
module Code_error = Code_error
module Comparable = Comparable
module Exn_with_backtrace = Exn_with_backtrace
module Fpath = Path
module Int = Int
module Table = Table
module Tuple = Tuple
Expand Down
1 change: 0 additions & 1 deletion ocaml-lsp-server/src/merlin_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,6 @@ module Process = struct
~message:"dune binary not found"
())
| Some prog ->
let prog = Fpath.to_string prog in
let stdin_r, stdin_w = Unix.pipe () in
let stdout_r, stdout_w = Unix.pipe () in
Unix.set_close_on_exec stdin_w;
Expand Down
3 changes: 1 addition & 2 deletions ocaml-lsp-server/src/ocamlformat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,8 +136,7 @@ let formatter doc =
| `Other -> Code_error.raise "unable to format non merlin document" []))
;;

let exec cancel bin args stdin =
let refmt = Fpath.to_string bin in
let exec cancel refmt args stdin =
let+ res, cancel = run_command cancel refmt stdin args in
match cancel with
| Cancelled () ->
Expand Down
3 changes: 1 addition & 2 deletions ocaml-lsp-server/src/ocamlformat_rpc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ module Process : sig

val create
: logger:(type_:MessageType.t -> message:string -> unit Fiber.t)
-> bin:Fpath.t
-> bin:string
-> unit
-> (t, [> `No_process ]) result Fiber.t

Expand Down Expand Up @@ -62,7 +62,6 @@ end = struct
;;

let create ~logger ~bin () =
let bin = Fpath.to_string bin in
let* pid, stdout, stdin =
let stdin_i, stdin_o = Unix.pipe ~cloexec:true () in
let stdout_i, stdout_o = Unix.pipe ~cloexec:true () in
Expand Down

0 comments on commit 3b5d4e8

Please sign in to comment.