Skip to content

Commit

Permalink
Move log function out of OCF thread
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Jun 29, 2021
1 parent 003d1f9 commit 5a79b4d
Showing 1 changed file with 8 additions and 11 deletions.
19 changes: 8 additions & 11 deletions ocaml-lsp-server/src/ocamlformat_rpc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,22 +41,19 @@ let configure process =
editors that use the server. *)
match
Scheduler.async io_thread (fun () ->
match
Ocamlformat_rpc_lib.config
[ ("module-item-spacing", "compact"); ("margin", "64") ]
client
with
| Ok () -> ()
| Error (`Msg msg) ->
Log.log ~section:"ocamlformat" (fun () ->
Log.msg "An error occured while configuring ocamlformat"
[ ("msg", `String msg) ]))
Ocamlformat_rpc_lib.config
[ ("module-item-spacing", "compact"); ("margin", "64") ]
client)
with
| Error `Stopped -> Fiber.return ()
| Ok res -> (
let+ res = Scheduler.await_no_cancel res in
match res with
| Ok s -> s
| Ok (Ok ()) -> ()
| Ok (Error (`Msg msg)) ->
Log.log ~section:"ocamlformat" (fun () ->
Log.msg "An error occured while configuring ocamlformat"
[ ("msg", `String msg) ])
| Error e -> Exn_with_backtrace.reraise e)

let start_exn ?io_thread t =
Expand Down

0 comments on commit 5a79b4d

Please sign in to comment.