@@ -190,18 +190,11 @@ module Process = struct
190190 { pid; initial_cwd; stdin; stdout; session }
191191end
192192
193- type t =
193+ type db =
194194 { running : (string , Process .t ) Table .t
195195 ; pool : Fiber.Pool .t
196196 }
197197
198- let create () =
199- { running = Table. create (module String ) 0 ; pool = Fiber.Pool. create () }
200-
201- let run t = Fiber.Pool. run t.pool
202-
203- let stop t = Fiber.Pool. stop t.pool
204-
205198let get_process t ~dir =
206199 match Table. find t.running dir with
207200 | Some p -> Fiber. return p
@@ -318,40 +311,49 @@ let find_project_context start_dir =
318311 in
319312 loop None start_dir
320313
321- module Ref = struct
322- type nonrec t =
323- { path : string
324- ; directory : string
325- ; initial : Mconfig .t
326- ; db : t
314+ type nonrec t =
315+ { path : string
316+ ; directory : string
317+ ; initial : Mconfig .t
318+ ; db : db
319+ }
320+
321+ let destroy _ = Fiber. return ()
322+
323+ let create db path =
324+ let path =
325+ let path = Uri. to_path path in
326+ Misc. canonicalize_filename path
327+ in
328+ let directory = Filename. dirname path in
329+ let initial =
330+ let filename = Filename. basename path in
331+ let init = Mconfig. initial in
332+ { init with
333+ ocaml = { init.ocaml with real_paths = false }
334+ ; query = { init.query with filename; directory }
327335 }
336+ in
337+ { path; directory; initial; db }
328338
329- let destroy _ = Fiber. return ()
339+ let config (t : t ) : Mconfig.t Fiber.t =
340+ let * () = Fiber. return () in
341+ match find_project_context t.directory with
342+ | None -> Fiber. return t.initial
343+ | Some (ctxt , config_path ) ->
344+ let + dot, failures = get_config t.db ctxt t.path in
345+ let merlin = Config. merge dot t.initial.merlin failures config_path in
346+ Mconfig. normalize { t.initial with merlin }
330347
331- let create db path =
332- let path =
333- let path = Uri. to_path path in
334- Misc. canonicalize_filename path
335- in
336- let directory = Filename. dirname path in
337- let initial =
338- let filename = Filename. basename path in
339- let init = Mconfig. initial in
340- { init with
341- ocaml = { init.ocaml with real_paths = false }
342- ; query = { init.query with filename; directory }
343- }
344- in
345- { path; directory; initial; db }
346-
347- let config (t : t ) : Mconfig.t Fiber.t =
348- let * () = Fiber. return () in
349- match find_project_context t.directory with
350- | None -> Fiber. return t.initial
351- | Some (ctxt , config_path ) ->
352- let + dot, failures = get_config t.db ctxt t.path in
353- let merlin = Config. merge dot t.initial.merlin failures config_path in
354- Mconfig. normalize { t.initial with merlin }
355- end
348+ module DB = struct
349+ type t = db
356350
357- let get t uri = Ref. create t uri
351+ let get t uri = create t uri
352+
353+ let create () =
354+ { running = Table. create (module String ) 0 ; pool = Fiber.Pool. create () }
355+
356+ let run t = Fiber.Pool. run t.pool
357+
358+ let stop t = Fiber.Pool. stop t.pool
359+ end
0 commit comments