Skip to content

Commit 6a38d66

Browse files
committed
chore: update ocamlformat to 0.21.0
1 parent 7038745 commit 6a38d66

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

45 files changed

+753
-1579
lines changed

.ocamlformat

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1-
version=0.19.0
1+
version=0.21.0
2+
profile=conventional
3+
ocaml-version=4.14.0
24
break-separators=before
35
dock-collection-brackets=false
46
break-sequences=true
@@ -8,12 +10,12 @@ let-and=sparse
810
sequence-style=terminator
911
type-decl=sparse
1012
wrap-comments=true
11-
if-then-else=k-r
1213
let-and=sparse
1314
space-around-records
1415
space-around-lists
1516
space-around-arrays
1617
cases-exp-indent=2
17-
break-cases=all
18+
break-cases=fit-or-vertical
1819
indicate-nested-or-patterns=unsafe-no
1920
parse-docstrings=true
21+
module-item-spacing=sparse

fiber-test/fiber_test.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,8 @@ let test ?(expect_never = false) to_dyn f =
4141
in
4242
Fiber.with_error_handler f ~on_error
4343
in
44-
(try Scheduler.run (Scheduler.create ()) f |> to_dyn |> print_dyn with
45-
| Scheduler.Never -> never_raised := true);
44+
(try Scheduler.run (Scheduler.create ()) f |> to_dyn |> print_dyn
45+
with Scheduler.Never -> never_raised := true);
4646
match (!never_raised, expect_never) with
4747
| false, false ->
4848
(* We don't raise in this case b/c we assume something else is being

jsonrpc-fiber/src/import.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -64,8 +64,7 @@ module Log = struct
6464
(match message.payload with
6565
| [] -> ()
6666
| fields -> Format.fprintf !out "%a@." Json.pp (`Assoc fields));
67-
Format.pp_print_flush !out ()
68-
)
67+
Format.pp_print_flush !out ())
6968
end
7069

7170
let sprintf = Printf.sprintf

jsonrpc-fiber/src/jsonrpc_fiber.ml

Lines changed: 6 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -23,12 +23,9 @@ module Sender = struct
2323

2424
let send t (r : Response.t) : unit Fiber.t =
2525
Fiber.of_thunk (fun () ->
26-
if t.called then
27-
Code_error.raise "cannot send response twice" []
28-
else if not (Id.equal t.for_ r.id) then
29-
Code_error.raise "invalid id" []
30-
else
31-
t.called <- true;
26+
if t.called then Code_error.raise "cannot send response twice" []
27+
else if not (Id.equal t.for_ r.id) then Code_error.raise "invalid id" []
28+
else t.called <- true;
3229
t.send r)
3330
end
3431

@@ -122,8 +119,7 @@ struct
122119

123120
let stop_pending_requests t =
124121
Fiber.of_thunk (fun () ->
125-
if t.pending_requests_stopped then
126-
Fiber.return ()
122+
if t.pending_requests_stopped then Fiber.return ()
127123
else (
128124
t.pending_requests_stopped <- true;
129125
let to_cancel =
@@ -132,8 +128,7 @@ struct
132128
in
133129
Id.Table.clear t.pending;
134130
Fiber.parallel_iter to_cancel ~f:(fun ivar ->
135-
Fiber.Ivar.fill ivar (Error `Stopped))
136-
))
131+
Fiber.Ivar.fill ivar (Error `Stopped))))
137132

138133
let create ?(on_request = on_request_fail)
139134
?(on_notification = on_notification_fail) ~name chan state =
@@ -214,8 +209,7 @@ struct
214209
Fiber.map_reduce_errors
215210
(module Stdune.Monoid.Unit)
216211
~on_error:(fun exn_bt ->
217-
if !sent then
218-
(* TODO log *)
212+
if !sent then (* TODO log *)
219213
Fiber.return ()
220214
else
221215
let response = response_of_exn r.id exn_bt in

jsonrpc-fiber/test/jsonrpc_fiber_tests.ml

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -27,10 +27,8 @@ let no_output () =
2727
let received_none = ref false in
2828
Out.create (function
2929
| None ->
30-
if !received_none then
31-
failwith "received None more than once"
32-
else
33-
received_none := true;
30+
if !received_none then failwith "received None more than once"
31+
else received_none := true;
3432
Fiber.return ()
3533
| Some _ -> failwith "unexpected element")
3634

@@ -158,9 +156,8 @@ let%expect_test "concurrent requests" =
158156
let self = Context.session c in
159157
print_endline "waitee: stopping";
160158
let+ () = Jrpc.stop self in
161-
print_endline "waitee: stopped"
162-
) else
163-
Fiber.return ())
159+
print_endline "waitee: stopped")
160+
else Fiber.return ())
164161
in
165162
let state = Context.state c in
166163
Fiber.return (response, state)

jsonrpc/src/jsonrpc.ml

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -95,10 +95,8 @@ module Message = struct
9595
let jsonrpc =
9696
Json.field_exn fields Constant.jsonrpc Json.Conv.string_of_yojson
9797
in
98-
if jsonrpc = Constant.jsonrpcv then
99-
{ method_; params; id }
100-
else
101-
Json.error "invalid version" json
98+
if jsonrpc = Constant.jsonrpcv then { method_; params; id }
99+
else Json.error "invalid version" json
102100
| _ -> Json.error "invalid request" json
103101

104102
let yojson_of_either t : Json.t = yojson_of_t (Option.map ~f:Id.yojson_of_t) t
@@ -237,8 +235,7 @@ module Response = struct
237235
let jsonrpc =
238236
Json.field_exn fields Constant.jsonrpc Json.Conv.string_of_yojson
239237
in
240-
if jsonrpc <> Constant.jsonrpcv then
241-
Json.error "Invalid response" json
238+
if jsonrpc <> Constant.jsonrpcv then Json.error "Invalid response" json
242239
else
243240
match Json.field fields Constant.result (fun x -> x) with
244241
| Some res -> { id; result = Ok res }

lsp-fiber/src/import.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,8 +31,7 @@ module Log = struct
3131
(match message.payload with
3232
| [] -> ()
3333
| fields -> Format.fprintf !out "%a@." Json.pp (`Assoc fields));
34-
Format.pp_print_flush !out ()
35-
)
34+
Format.pp_print_flush !out ())
3635
end
3736

3837
let sprintf = Stdune.sprintf

lsp-fiber/src/rpc.ml

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -414,8 +414,8 @@ module Server = struct
414414
t.state <- Running;
415415
(* XXX Should we wait for the waiter of initialized to finish? *)
416416
let* () = Fiber.Ivar.fill t.initialized i in
417-
Fiber.return result
418-
) else
417+
Fiber.return result)
418+
else
419419
let code = Response.Error.Code.InvalidRequest in
420420
let message = "already initialized" in
421421
raise
@@ -428,8 +428,7 @@ module Server = struct
428428
raise
429429
(Jsonrpc.Response.Error.E
430430
(Jsonrpc.Response.Error.make ~code ~message ()))
431-
else
432-
handler.h_on_request.on_request t in_r)
431+
else handler.h_on_request.on_request t in_r)
433432

434433
let make (type s) (handler : s Handler.t) io (initial_state : s) =
435434
let h_on_request : _ Handler.on_request =

lsp/bin/ocaml/json_gen.ml

Lines changed: 3 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -87,8 +87,7 @@ module Enum = struct
8787
Create (Constr { tag = "Other"; poly; args = [ Create s ] })
8888
in
8989
clauses @ [ (pat, make) ]
90-
else
91-
clauses
90+
else clauses
9291
in
9392
let msg =
9493
sprintf "Invalid value. Expected one of: %s"
@@ -116,8 +115,7 @@ module Enum = struct
116115
Create (Constr { tag = "String"; poly = true; args = [ Create s ] })
117116
in
118117
clauses @ [ (pat, make) ]
119-
else
120-
clauses
118+
else clauses
121119
in
122120
Match (Create (Ident name), clauses)
123121
in
@@ -138,10 +136,7 @@ module Poly_variant = struct
138136
let split_clauses constrs =
139137
let json_constrs, untagged_constrs =
140138
List.partition_map constrs ~f:(fun x ->
141-
if is_json_constr x then
142-
Left x
143-
else
144-
Right x)
139+
if is_json_constr x then Left x else Right x)
145140
in
146141
{ json_constrs; untagged_constrs }
147142

lsp/bin/ocaml/ml.ml

Lines changed: 7 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -31,12 +31,7 @@ module Kind = struct
3131
end
3232

3333
let is_kw = function
34-
| "type"
35-
| "method"
36-
| "end"
37-
| "to"
38-
| "external" ->
39-
true
34+
| "type" | "method" | "end" | "to" | "external" -> true
4035
| _ -> false
4136

4237
module Arg = struct
@@ -369,11 +364,7 @@ module Expr = struct
369364
let pp_constr f { tag; poly; args } =
370365
let tag =
371366
let tag = String.capitalize tag in
372-
Pp.verbatim
373-
(if poly then
374-
"`" ^ tag
375-
else
376-
tag)
367+
Pp.verbatim (if poly then "`" ^ tag else tag)
377368
in
378369
match args with
379370
| [] -> tag
@@ -402,10 +393,7 @@ module Expr = struct
402393
| Bool b -> Pp.textf "%b" b
403394
| Int i ->
404395
let pp = Pp.textf "%i" i in
405-
if i < 0 then
406-
W.surround `Paren pp
407-
else
408-
pp
396+
if i < 0 then W.surround `Paren pp else pp
409397
| String s -> Pp.textf "%S" s
410398
| Ident s -> Pp.verbatim s
411399
| Cons _ -> assert false
@@ -419,10 +407,8 @@ module Expr = struct
419407
Pp.concat_map fields
420408
~sep:(Pp.verbatim ";" ++ Pp.space)
421409
~f:(fun (name, expr) ->
422-
if expr = Create (Ident name) then
423-
pp expr
424-
else
425-
Pp.verbatim name ++ Pp.space ++ Pp.verbatim "=" ++ pp expr)
410+
if expr = Create (Ident name) then pp expr
411+
else Pp.verbatim name ++ Pp.space ++ Pp.verbatim "=" ++ pp expr)
426412
in
427413
W.surround `Curly record
428414
| Constr c -> pp_constr pp c
@@ -493,14 +479,12 @@ module Expr = struct
493479
| Labeled (l, r) ->
494480
if l = r then
495481
Pp.concat [ Pp.textf "~(%s :" l; typ; Pp.verbatim ")" ]
496-
else
497-
assert false
482+
else assert false
498483
| Optional (l, r) ->
499484
if l = r then
500485
Pp.concat
501486
[ Pp.textf "?(%s :" l; typ; Pp.space; Pp.verbatim "option)" ]
502-
else
503-
assert false)
487+
else assert false)
504488
in
505489
let body = pp body in
506490
let type_ = Type.pp type_ ~kind in

0 commit comments

Comments
 (0)