Skip to content

Commit b0f6330

Browse files
authored
refactor: remove uses of [Stdune.Fdecl] (#1399)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 4ff26ca commit b0f6330

File tree

5 files changed

+29
-5
lines changed

5 files changed

+29
-5
lines changed

lsp-fiber/src/import.ml

Lines changed: 25 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,32 @@
11
module List = Stdlib.ListLabels
22
module Code_error = Stdune.Code_error
3-
module Fdecl = Stdune.Fdecl
43
module Header = Lsp.Header
54
module Io = Lsp.Io
65

6+
module Fdecl : sig
7+
type 'a t
8+
9+
val get : 'a t -> 'a
10+
val set : 'a t -> 'a -> unit
11+
val create : unit -> 'a t
12+
end = struct
13+
type 'a t = 'a option ref
14+
15+
let create () = ref None
16+
17+
let set t x =
18+
match !t with
19+
| Some _ -> invalid_arg "Fdecl.create: already set"
20+
| None -> t := Some x
21+
;;
22+
23+
let get t =
24+
match !t with
25+
| None -> invalid_arg "Fdecl.get: not set"
26+
| Some t -> t
27+
;;
28+
end
29+
730
module Json = struct
831
include Lsp.Import.Json
932

@@ -74,7 +97,7 @@ module Log = struct
7497
;;
7598
end
7699

77-
let sprintf = Stdune.sprintf
100+
let sprintf = Printf.sprintf
78101

79102
module Types = Lsp.Types
80103
module Client_request = Lsp.Client_request

lsp-fiber/src/lsp_fiber.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,4 +7,5 @@ module Json = Import.Json
77

88
module Private = struct
99
module Log = Import.Log
10+
module Fdecl = Import.Fdecl
1011
end

lsp-fiber/src/rpc.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -219,7 +219,7 @@ struct
219219
let t =
220220
{ io
221221
; state = Waiting_for_init
222-
; session = Fdecl.create Dyn.opaque
222+
; session = Fdecl.create ()
223223
; initialized = Fiber.Ivar.create ()
224224
; req_id = 1
225225
; pending = Table.create 32

ocaml-lsp-server/src/import.ml

Lines changed: 1 addition & 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 Fdecl = Fdecl
109
module Fpath = Path
1110
module Int = Int
1211
module Table = Table
@@ -212,6 +211,7 @@ module Format = Merlin_utils.Std.Format
212211
include struct
213212
open Lsp_fiber
214213
module Log = Private.Log
214+
module Fdecl = Private.Fdecl
215215
module Reply = Rpc.Reply
216216
module Server = Server
217217
module Lazy_fiber = Lsp_fiber.Lazy_fiber

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -787,7 +787,7 @@ let on_notification server (notification : Client_notification.t) : State.t Fibe
787787

788788
let start stream =
789789
let detached = Fiber.Pool.create () in
790-
let server = Fdecl.create Dyn.opaque in
790+
let server = Fdecl.create () in
791791
let store = Document_store.make server detached in
792792
let handler =
793793
let on_request = { Server.Handler.on_request } in

0 commit comments

Comments
 (0)