Skip to content

Commit 6cde996

Browse files
authored
Upgrade (again) to OCamlformat 0.27.0 (#1444)
* Bump ocamlformat version and update nix flake * Promote formatting changes * Add commit to ignored revs
1 parent 643f590 commit 6cde996

Some content is hidden

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

70 files changed

+2625
-2335
lines changed

.git-blame-ignore-revs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,5 @@
77
ab49baa5873e7f0b9181dbed3ad89681f1e4bcee
88
# Upgrade to OCamlformat 0.26.1
99
1a6419bac3ce012deb9c6891e6b25e2486c33388
10+
# Upgrade to OCamlformat 0.27.0
11+
2ccbee5dd691690228307d3636e2f82c8cdb3902

.ocamlformat

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
1-
version=0.26.2
1+
version=0.27.0
22
profile=janestreet
33
ocaml-version=4.14.0

dune-project

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,7 @@ possible and does not make any assumptions about IO.
6464
astring
6565
camlp-streams
6666
(ppx_expect (and (>= v0.17.0) :with-test))
67-
(ocamlformat (and :with-test (= 0.26.2)))
67+
(ocamlformat (and :with-test (= 0.27.0)))
6868
(ocamlc-loc (>= 3.7.0))
6969
(pp (>= 1.1.2))
7070
(csexp (>= 1.5))

flake.lock

Lines changed: 13 additions & 47 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

jsonrpc-fiber/src/jsonrpc_fiber.ml

Lines changed: 11 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -137,11 +137,11 @@ struct
137137
;;
138138

139139
let create
140-
?(on_request = on_request_fail)
141-
?(on_notification = on_notification_fail)
142-
~name
143-
chan
144-
state
140+
?(on_request = on_request_fail)
141+
?(on_notification = on_notification_fail)
142+
~name
143+
chan
144+
state
145145
=
146146
let pending = Id.Table.create 10 in
147147
{ chan
@@ -274,8 +274,8 @@ struct
274274
let* () =
275275
Fiber.fork_and_join_unit
276276
(fun () ->
277-
let* () = loop () in
278-
Fiber.Pool.stop later)
277+
let* () = loop () in
278+
Fiber.Pool.stop later)
279279
(fun () -> Fiber.Pool.run later)
280280
in
281281
close t)
@@ -358,11 +358,10 @@ struct
358358
let pending = !batch in
359359
batch := [];
360360
let pending, ivars =
361-
List.fold_left pending ~init:([], []) ~f:(fun (pending, ivars) ->
362-
function
363-
| `Notification n -> Jsonrpc.Packet.Notification n :: pending, ivars
364-
| `Request ((r : Request.t), ivar) ->
365-
Jsonrpc.Packet.Request r :: pending, (r.id, ivar) :: ivars)
361+
List.fold_left pending ~init:([], []) ~f:(fun (pending, ivars) -> function
362+
| `Notification n -> Jsonrpc.Packet.Notification n :: pending, ivars
363+
| `Request ((r : Request.t), ivar) ->
364+
Jsonrpc.Packet.Request r :: pending, (r.id, ivar) :: ivars)
366365
in
367366
List.iter ivars ~f:(fun (id, ivar) -> register_request_ivar t id ivar);
368367
Chan.send t.chan pending)

jsonrpc-fiber/test/jsonrpc_fiber_tests.ml

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,8 @@ let%expect_test "start and stop server" =
4141
Fiber.fork_and_join_unit (fun () -> run) (fun () -> Jrpc.stop jrpc)
4242
in
4343
let () = Fiber_test.test Dyn.opaque run in
44-
[%expect {|
44+
[%expect
45+
{|
4546
<opaque> |}]
4647
;;
4748

@@ -62,7 +63,8 @@ let%expect_test "server accepts notifications" =
6263
Jrpc.run jrpc
6364
in
6465
Fiber_test.test Dyn.opaque run;
65-
[%expect {|
66+
[%expect
67+
{|
6668
received notification
6769
<opaque> |}]
6870
;;
@@ -99,7 +101,8 @@ let%expect_test "serving requests" =
99101
print_endline (Yojson.Safe.pretty_to_string ~std:false json))
100102
in
101103
Fiber_test.test Dyn.opaque run;
102-
[%expect {|
104+
[%expect
105+
{|
103106
{ "id": 1, "jsonrpc": "2.0", "result": "response" }
104107
<opaque> |}]
105108
;;

jsonrpc/src/jsonrpc.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -247,8 +247,8 @@ module Packet = struct
247247
| Batch_call r ->
248248
`List
249249
(List.map r ~f:(function
250-
| `Request r -> Request.yojson_of_t r
251-
| `Notification r -> Notification.yojson_of_t r))
250+
| `Request r -> Request.yojson_of_t r
251+
| `Notification r -> Notification.yojson_of_t r))
252252
;;
253253

254254
let t_of_fields (fields : (string * Json.t) list) =

lsp-fiber/src/rpc.ml

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -147,9 +147,9 @@ struct
147147
;;
148148

149149
let make
150-
?(on_request = on_request_default)
151-
?(on_notification = on_notification_default)
152-
()
150+
?(on_request = on_request_default)
151+
?(on_notification = on_notification_default)
152+
()
153153
=
154154
{ h_on_request = on_request; h_on_notification = on_notification }
155155
;;
@@ -176,9 +176,9 @@ struct
176176
Lazy.force remove;
177177
exn))
178178
(fun () ->
179-
Fiber.Var.set cancel_token cancel (fun () ->
180-
Table.replace t.pending req.id cancel;
181-
h_on_request.on_request t r))
179+
Fiber.Var.set cancel_token cancel (fun () ->
180+
Table.replace t.pending req.id cancel;
181+
h_on_request.on_request t r))
182182
in
183183
let to_response x =
184184
Jsonrpc.Response.ok req.id (In_request.yojson_of_result r x)
@@ -192,8 +192,8 @@ struct
192192
let f send =
193193
Fiber.finalize
194194
(fun () ->
195-
Fiber.Var.set cancel_token cancel (fun () ->
196-
k (fun r -> send (to_response r))))
195+
Fiber.Var.set cancel_token cancel (fun () ->
196+
k (fun r -> send (to_response r))))
197197
~finally:(fun () ->
198198
Lazy.force remove;
199199
Fiber.return ())
@@ -265,12 +265,12 @@ struct
265265
cancel
266266
~on_cancel:(fun () -> on_cancel jsonrpc_req.id)
267267
(fun () ->
268-
let+ resp = Session.request (Fdecl.get t.session) jsonrpc_req in
269-
match resp.result with
270-
| Error { code = RequestCancelled; _ } -> `Cancelled
271-
| Ok _ when Fiber.Cancel.fired cancel -> `Cancelled
272-
| Ok s -> `Ok (Out_request.response_of_json req s)
273-
| Error e -> raise (Jsonrpc.Response.Error.E e))
268+
let+ resp = Session.request (Fdecl.get t.session) jsonrpc_req in
269+
match resp.result with
270+
| Error { code = RequestCancelled; _ } -> `Cancelled
271+
| Ok _ when Fiber.Cancel.fired cancel -> `Cancelled
272+
| Ok s -> `Ok (Out_request.response_of_json req s)
273+
| Error e -> raise (Jsonrpc.Response.Error.E e))
274274
in
275275
match cancel_status with
276276
| Cancelled () -> `Cancelled
@@ -331,8 +331,8 @@ struct
331331
let start_loop t =
332332
Fiber.fork_and_join_unit
333333
(fun () ->
334-
let* () = Session.run (Fdecl.get t.session) in
335-
Fiber.Pool.stop t.detached)
334+
let* () = Session.run (Fdecl.get t.session) in
335+
Fiber.Pool.stop t.detached)
336336
(fun () -> Fiber.Pool.run t.detached)
337337
;;
338338

lsp-fiber/test/lsp_fiber_test.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -6,11 +6,11 @@ open Lsp_fiber
66
module Test = struct
77
module Client = struct
88
let run
9-
?(capabilities = ClientCapabilities.create ())
10-
?on_request
11-
?on_notification
12-
state
13-
(in_, out)
9+
?(capabilities = ClientCapabilities.create ())
10+
?on_request
11+
?on_notification
12+
state
13+
(in_, out)
1414
=
1515
let initialize = InitializeParams.create ~capabilities () in
1616
let client =

lsp/bin/cinaps.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -108,8 +108,8 @@ let ocaml =
108108
(Metamodel_lsp.t ()
109109
|> preprocess_metamodel#t
110110
|> (fun metamodel ->
111-
let db = Metamodel.Entity.DB.create metamodel in
112-
expand_superclasses db metamodel)
111+
let db = Metamodel.Entity.DB.create metamodel in
112+
expand_superclasses db metamodel)
113113
|> Typescript.of_metamodel
114114
|> Ocaml.of_typescript)
115115
;;

0 commit comments

Comments
 (0)