Skip to content

Commit

Permalink
Upgrade (again) to OCamlformat 0.27.0 (#1444)
Browse files Browse the repository at this point in the history
* Bump ocamlformat version and update nix flake

* Promote formatting changes

* Add commit to ignored revs
  • Loading branch information
voodoos authored Jan 10, 2025
1 parent 643f590 commit 6cde996
Show file tree
Hide file tree
Showing 70 changed files with 2,625 additions and 2,335 deletions.
2 changes: 2 additions & 0 deletions .git-blame-ignore-revs
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,5 @@
ab49baa5873e7f0b9181dbed3ad89681f1e4bcee
# Upgrade to OCamlformat 0.26.1
1a6419bac3ce012deb9c6891e6b25e2486c33388
# Upgrade to OCamlformat 0.27.0
2ccbee5dd691690228307d3636e2f82c8cdb3902
2 changes: 1 addition & 1 deletion .ocamlformat
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
version=0.26.2
version=0.27.0
profile=janestreet
ocaml-version=4.14.0
2 changes: 1 addition & 1 deletion dune-project
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ possible and does not make any assumptions about IO.
astring
camlp-streams
(ppx_expect (and (>= v0.17.0) :with-test))
(ocamlformat (and :with-test (= 0.26.2)))
(ocamlformat (and :with-test (= 0.27.0)))
(ocamlc-loc (>= 3.7.0))
(pp (>= 1.1.2))
(csexp (>= 1.5))
Expand Down
60 changes: 13 additions & 47 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

23 changes: 11 additions & 12 deletions jsonrpc-fiber/src/jsonrpc_fiber.ml
Original file line number Diff line number Diff line change
Expand Up @@ -137,11 +137,11 @@ struct
;;

let create
?(on_request = on_request_fail)
?(on_notification = on_notification_fail)
~name
chan
state
?(on_request = on_request_fail)
?(on_notification = on_notification_fail)
~name
chan
state
=
let pending = Id.Table.create 10 in
{ chan
Expand Down Expand Up @@ -274,8 +274,8 @@ struct
let* () =
Fiber.fork_and_join_unit
(fun () ->
let* () = loop () in
Fiber.Pool.stop later)
let* () = loop () in
Fiber.Pool.stop later)
(fun () -> Fiber.Pool.run later)
in
close t)
Expand Down Expand Up @@ -358,11 +358,10 @@ struct
let pending = !batch in
batch := [];
let pending, ivars =
List.fold_left pending ~init:([], []) ~f:(fun (pending, ivars) ->
function
| `Notification n -> Jsonrpc.Packet.Notification n :: pending, ivars
| `Request ((r : Request.t), ivar) ->
Jsonrpc.Packet.Request r :: pending, (r.id, ivar) :: ivars)
List.fold_left pending ~init:([], []) ~f:(fun (pending, ivars) -> function
| `Notification n -> Jsonrpc.Packet.Notification n :: pending, ivars
| `Request ((r : Request.t), ivar) ->
Jsonrpc.Packet.Request r :: pending, (r.id, ivar) :: ivars)
in
List.iter ivars ~f:(fun (id, ivar) -> register_request_ivar t id ivar);
Chan.send t.chan pending)
Expand Down
9 changes: 6 additions & 3 deletions jsonrpc-fiber/test/jsonrpc_fiber_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,8 @@ let%expect_test "start and stop server" =
Fiber.fork_and_join_unit (fun () -> run) (fun () -> Jrpc.stop jrpc)
in
let () = Fiber_test.test Dyn.opaque run in
[%expect {|
[%expect
{|
<opaque> |}]
;;

Expand All @@ -62,7 +63,8 @@ let%expect_test "server accepts notifications" =
Jrpc.run jrpc
in
Fiber_test.test Dyn.opaque run;
[%expect {|
[%expect
{|
received notification
<opaque> |}]
;;
Expand Down Expand Up @@ -99,7 +101,8 @@ let%expect_test "serving requests" =
print_endline (Yojson.Safe.pretty_to_string ~std:false json))
in
Fiber_test.test Dyn.opaque run;
[%expect {|
[%expect
{|
{ "id": 1, "jsonrpc": "2.0", "result": "response" }
<opaque> |}]
;;
Expand Down
4 changes: 2 additions & 2 deletions jsonrpc/src/jsonrpc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -247,8 +247,8 @@ module Packet = struct
| Batch_call r ->
`List
(List.map r ~f:(function
| `Request r -> Request.yojson_of_t r
| `Notification r -> Notification.yojson_of_t r))
| `Request r -> Request.yojson_of_t r
| `Notification r -> Notification.yojson_of_t r))
;;

let t_of_fields (fields : (string * Json.t) list) =
Expand Down
32 changes: 16 additions & 16 deletions lsp-fiber/src/rpc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -147,9 +147,9 @@ struct
;;

let make
?(on_request = on_request_default)
?(on_notification = on_notification_default)
()
?(on_request = on_request_default)
?(on_notification = on_notification_default)
()
=
{ h_on_request = on_request; h_on_notification = on_notification }
;;
Expand All @@ -176,9 +176,9 @@ struct
Lazy.force remove;
exn))
(fun () ->
Fiber.Var.set cancel_token cancel (fun () ->
Table.replace t.pending req.id cancel;
h_on_request.on_request t r))
Fiber.Var.set cancel_token cancel (fun () ->
Table.replace t.pending req.id cancel;
h_on_request.on_request t r))
in
let to_response x =
Jsonrpc.Response.ok req.id (In_request.yojson_of_result r x)
Expand All @@ -192,8 +192,8 @@ struct
let f send =
Fiber.finalize
(fun () ->
Fiber.Var.set cancel_token cancel (fun () ->
k (fun r -> send (to_response r))))
Fiber.Var.set cancel_token cancel (fun () ->
k (fun r -> send (to_response r))))
~finally:(fun () ->
Lazy.force remove;
Fiber.return ())
Expand Down Expand Up @@ -265,12 +265,12 @@ struct
cancel
~on_cancel:(fun () -> on_cancel jsonrpc_req.id)
(fun () ->
let+ resp = Session.request (Fdecl.get t.session) jsonrpc_req in
match resp.result with
| Error { code = RequestCancelled; _ } -> `Cancelled
| Ok _ when Fiber.Cancel.fired cancel -> `Cancelled
| Ok s -> `Ok (Out_request.response_of_json req s)
| Error e -> raise (Jsonrpc.Response.Error.E e))
let+ resp = Session.request (Fdecl.get t.session) jsonrpc_req in
match resp.result with
| Error { code = RequestCancelled; _ } -> `Cancelled
| Ok _ when Fiber.Cancel.fired cancel -> `Cancelled
| Ok s -> `Ok (Out_request.response_of_json req s)
| Error e -> raise (Jsonrpc.Response.Error.E e))
in
match cancel_status with
| Cancelled () -> `Cancelled
Expand Down Expand Up @@ -331,8 +331,8 @@ struct
let start_loop t =
Fiber.fork_and_join_unit
(fun () ->
let* () = Session.run (Fdecl.get t.session) in
Fiber.Pool.stop t.detached)
let* () = Session.run (Fdecl.get t.session) in
Fiber.Pool.stop t.detached)
(fun () -> Fiber.Pool.run t.detached)
;;

Expand Down
10 changes: 5 additions & 5 deletions lsp-fiber/test/lsp_fiber_test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,11 @@ open Lsp_fiber
module Test = struct
module Client = struct
let run
?(capabilities = ClientCapabilities.create ())
?on_request
?on_notification
state
(in_, out)
?(capabilities = ClientCapabilities.create ())
?on_request
?on_notification
state
(in_, out)
=
let initialize = InitializeParams.create ~capabilities () in
let client =
Expand Down
4 changes: 2 additions & 2 deletions lsp/bin/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,8 +108,8 @@ let ocaml =
(Metamodel_lsp.t ()
|> preprocess_metamodel#t
|> (fun metamodel ->
let db = Metamodel.Entity.DB.create metamodel in
expand_superclasses db metamodel)
let db = Metamodel.Entity.DB.create metamodel in
expand_superclasses db metamodel)
|> Typescript.of_metamodel
|> Ocaml.of_typescript)
;;
Expand Down
8 changes: 4 additions & 4 deletions lsp/bin/metamodel/metamodel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -236,8 +236,8 @@ let rec type_ json =
field
"value"
(fun json ->
let fields = fields_conv json in
properties fields)
let fields = fields_conv json in
properties fields)
fields
in
Literal (Record fields)
Expand Down Expand Up @@ -354,8 +354,8 @@ module Entity = struct
type nonrec t = t String.Map.t

let create
({ structures; requests = _; notifications = _; enumerations; typeAliases } :
metamodel)
({ structures; requests = _; notifications = _; enumerations; typeAliases } :
metamodel)
: t
=
let structures =
Expand Down
2 changes: 1 addition & 1 deletion lsp/bin/ocaml/ml.mli
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ module Expr : sig
(** toplevel declartion (without the name) *)
type toplevel =
{ pat : (string Arg.t * Type.t) list
(** paterns and their types. types should be optional but they really
(** paterns and their types. types should be optional but they really
help the error messages if the generated code is incorrect *)
; type_ : Type.t (** useful to annotate the return types *)
; body : t
Expand Down
2 changes: 1 addition & 1 deletion lsp/bin/typescript/typescript.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ and field { Metamodel.name; optional; doc = _; type_ } : Ts_types.Unresolved.fie
;;

let structure
({ doc = _; extends = _; mixins = _; name; properties } : Metamodel.structure)
({ doc = _; extends = _; mixins = _; name; properties } : Metamodel.structure)
: Ts_types.Unresolved.t
=
let interface : Ts_types.Unresolved.interface =
Expand Down
5 changes: 3 additions & 2 deletions lsp/src/extension.ml
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,9 @@ module DebugEcho = struct
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| _ ->
if Ppx_yojson_conv_lib.( ! )
Ppx_yojson_conv_lib.Yojson_conv.record_check_extra_fields
if
Ppx_yojson_conv_lib.( ! )
Ppx_yojson_conv_lib.Yojson_conv.record_check_extra_fields
then extra := field_name :: Ppx_yojson_conv_lib.( ! ) extra
else ());
iter tail
Expand Down
12 changes: 6 additions & 6 deletions lsp/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -168,12 +168,12 @@ module Json = struct
;;

let literal_field
(type a)
(name : string)
(k : string)
(v : string)
(f : t -> a)
(json : t)
(type a)
(name : string)
(k : string)
(v : string)
(f : t -> a)
(json : t)
: a
=
match json with
Expand Down
5 changes: 3 additions & 2 deletions lsp/src/io.ml
Original file line number Diff line number Diff line change
Expand Up @@ -64,8 +64,9 @@ struct
| None -> loop chan content_length content_type
| Some (k, v) ->
let k = String.trim k in
if caseless_equal k content_length_lowercase
&& content_length = init_content_length
if
caseless_equal k content_length_lowercase
&& content_length = init_content_length
then (
let content_length = int_of_string_opt (String.trim v) in
match content_length with
Expand Down
Loading

0 comments on commit 6cde996

Please sign in to comment.