Skip to content

Commit

Permalink
Simplifie configuration hook
Browse files Browse the repository at this point in the history
  • Loading branch information
xvw committed Jun 5, 2024
1 parent 7f58e87 commit 68cb27e
Showing 1 changed file with 6 additions and 14 deletions.
20 changes: 6 additions & 14 deletions ocaml-lsp-server/src/document.ml
Original file line number Diff line number Diff line change
Expand Up @@ -132,22 +132,19 @@ module Single_pipeline : sig
-> f:(Mpipeline.t -> 'a)
-> ('a, Exn_with_backtrace.t) result Fiber.t

val use_with_post_config :
val use_with_config :
?name:string
-> t
-> doc:Text_document.t
-> config:Merlin_config.t
-> post_config:(Mconfig.t -> Mconfig.t)
-> config:Mconfig.t
-> f:(Mpipeline.t -> 'a)
-> ('a, Exn_with_backtrace.t) result Fiber.t
end = struct
type t = { thread : Lev_fiber.Thread.t } [@@unboxed]

let create thread = { thread }

let use_with_post_config ?name t ~doc ~config ~post_config ~f =
let* config = Merlin_config.config config in
let config = post_config config in
let use_with_config ?name t ~doc ~config ~f =
let make_pipeline =
let source = Msource.make (Text_document.text doc) in
fun () -> Mpipeline.make config source
Expand Down Expand Up @@ -185,7 +182,8 @@ end = struct
Ok res

let use ?name t ~doc ~config ~f =
use_with_post_config ?name t ~doc ~config ~post_config:Fun.id ~f
let* config = Merlin_config.config config in
use_with_config ?name t ~doc ~config ~f
end

type merlin =
Expand Down Expand Up @@ -290,13 +288,7 @@ module Merlin = struct
Single_pipeline.use ?name t.pipeline ~doc:t.tdoc ~config:t.merlin_config ~f

let with_configurable_pipeline ?name ~config (t : t) f =
Single_pipeline.use_with_post_config
?name
t.pipeline
~post_config:(fun _ -> config)
~doc:t.tdoc
~config:t.merlin_config
~f
Single_pipeline.use_with_config ?name t.pipeline ~doc:t.tdoc ~config ~f

let mconfig (t : t) = Merlin_config.config t.merlin_config

Expand Down

0 comments on commit 68cb27e

Please sign in to comment.