Skip to content

Commit

Permalink
refactor: remove uses of [Stdune.Fdecl] (#1399)
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 4ff26ca commit b0f6330
Show file tree
Hide file tree
Showing 5 changed files with 29 additions and 5 deletions.
27 changes: 25 additions & 2 deletions lsp-fiber/src/import.ml
Original file line number Diff line number Diff line change
@@ -1,9 +1,32 @@
module List = Stdlib.ListLabels
module Code_error = Stdune.Code_error
module Fdecl = Stdune.Fdecl
module Header = Lsp.Header
module Io = Lsp.Io

module Fdecl : sig
type 'a t

val get : 'a t -> 'a
val set : 'a t -> 'a -> unit
val create : unit -> 'a t
end = struct
type 'a t = 'a option ref

let create () = ref None

let set t x =
match !t with
| Some _ -> invalid_arg "Fdecl.create: already set"
| None -> t := Some x
;;

let get t =
match !t with
| None -> invalid_arg "Fdecl.get: not set"
| Some t -> t
;;
end

module Json = struct
include Lsp.Import.Json

Expand Down Expand Up @@ -74,7 +97,7 @@ module Log = struct
;;
end

let sprintf = Stdune.sprintf
let sprintf = Printf.sprintf

module Types = Lsp.Types
module Client_request = Lsp.Client_request
Expand Down
1 change: 1 addition & 0 deletions lsp-fiber/src/lsp_fiber.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,4 +7,5 @@ module Json = Import.Json

module Private = struct
module Log = Import.Log
module Fdecl = Import.Fdecl
end
2 changes: 1 addition & 1 deletion lsp-fiber/src/rpc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -219,7 +219,7 @@ struct
let t =
{ io
; state = Waiting_for_init
; session = Fdecl.create Dyn.opaque
; session = Fdecl.create ()
; initialized = Fiber.Ivar.create ()
; req_id = 1
; pending = Table.create 32
Expand Down
2 changes: 1 addition & 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 Fdecl = Fdecl
module Fpath = Path
module Int = Int
module Table = Table
Expand Down Expand Up @@ -212,6 +211,7 @@ module Format = Merlin_utils.Std.Format
include struct
open Lsp_fiber
module Log = Private.Log
module Fdecl = Private.Fdecl
module Reply = Rpc.Reply
module Server = Server
module Lazy_fiber = Lsp_fiber.Lazy_fiber
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -787,7 +787,7 @@ let on_notification server (notification : Client_notification.t) : State.t Fibe

let start stream =
let detached = Fiber.Pool.create () in
let server = Fdecl.create Dyn.opaque in
let server = Fdecl.create () in
let store = Document_store.make server detached in
let handler =
let on_request = { Server.Handler.on_request } in
Expand Down

0 comments on commit b0f6330

Please sign in to comment.