Skip to content

Commit 9dc8de2

Browse files
authored
Upgrade OCamlformat to 0.26.1 (#1177)
1 parent 2ffaea0 commit 9dc8de2

26 files changed

+194
-196
lines changed

.git-blame-ignore-revs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,3 +3,7 @@
33
# add ocamlformat config `wrap-fun-args=false`
44

55
75504946eaa6f817550b649df508d61dde12bbda
6+
# Upgrade to OCamlformat 0.26.0
7+
ab49baa5873e7f0b9181dbed3ad89681f1e4bcee
8+
# Upgrade to OCamlformat 0.26.1
9+
1a6419bac3ce012deb9c6891e6b25e2486c33388

.ocamlformat

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
version=0.24.1
1+
version=0.26.1
22
profile=conventional
33
ocaml-version=4.14.0
44
break-separators=before

flake.nix

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -152,7 +152,7 @@
152152
buildInputs = (with pkgs;
153153
[
154154
# dev tools
155-
ocamlformat_0_24_1
155+
ocamlformat_0_26_1
156156
yarn
157157

158158
ocamlPackages.ppx_expect

lsp-fiber/src/rpc.ml

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -106,13 +106,14 @@ end
106106

107107
module Table = Stdlib.Hashtbl.Make (Jsonrpc.Id)
108108

109-
module Make (Initialize : sig
110-
type t
111-
end)
112-
(Out_request : Request_intf)
113-
(Out_notification : Notification_intf)
114-
(In_request : Request_intf)
115-
(In_notification : Notification_intf) =
109+
module Make
110+
(Initialize : sig
111+
type t
112+
end)
113+
(Out_request : Request_intf)
114+
(Out_notification : Notification_intf)
115+
(In_request : Request_intf)
116+
(In_notification : Notification_intf) =
116117
struct
117118
type 'a out_request = 'a Out_request.t
118119

lsp/bin/metamodel/metamodel.mli

Lines changed: 12 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -137,25 +137,24 @@ module Path : sig
137137
| Property of property * t
138138
end
139139

140-
class map :
141-
object
142-
method literal : Path.t -> literalType -> literalType
140+
class map : object
141+
method literal : Path.t -> literalType -> literalType
143142

144-
method property : Path.t -> property -> property
143+
method property : Path.t -> property -> property
145144

146-
method or_ : Path.t -> type_ list -> type_
145+
method or_ : Path.t -> type_ list -> type_
147146

148-
method type_ : Path.t -> type_ -> type_
147+
method type_ : Path.t -> type_ -> type_
149148

150-
method t : t -> t
149+
method t : t -> t
151150

152-
method request : request -> request
151+
method request : request -> request
153152

154-
method structure : structure -> structure
153+
method structure : structure -> structure
155154

156-
method notification : notification -> notification
155+
method notification : notification -> notification
157156

158-
method typeAlias : typeAlias -> typeAlias
157+
method typeAlias : typeAlias -> typeAlias
159158

160-
method enumeration : enumeration -> enumeration
161-
end
159+
method enumeration : enumeration -> enumeration
160+
end

lsp/bin/ocaml/ml.mli

Lines changed: 24 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -144,49 +144,48 @@ module Type : sig
144144
145145
['env] is a custom value threaded through the path. Parent nodes can use
146146
this to give child nodes context *)
147-
class virtual ['env, 'm] mapreduce :
148-
object ('self)
149-
method virtual empty : 'm
147+
class virtual ['env, 'm] mapreduce : object ('self)
148+
method virtual empty : 'm
150149

151-
method virtual plus : 'm -> 'm -> 'm
150+
method virtual plus : 'm -> 'm -> 'm
152151

153-
(** doesn't really to be here, but putting it here avoids passing [empty]
154-
and [plus] to a general purpose [fold_left_map]*)
155-
method private fold_left_map :
156-
'a. f:('a -> 'a * 'm) -> 'a list -> 'a list * 'm
152+
(** doesn't really to be here, but putting it here avoids passing [empty]
153+
and [plus] to a general purpose [fold_left_map]*)
154+
method private fold_left_map :
155+
'a. f:('a -> 'a * 'm) -> 'a list -> 'a list * 'm
157156

158-
method alias : 'env -> t -> decl * 'm
157+
method alias : 'env -> t -> decl * 'm
159158

160-
method app : 'env -> t -> t list -> t * 'm
159+
method app : 'env -> t -> t list -> t * 'm
161160

162-
method assoc : 'env -> t -> t -> t * 'm
161+
method assoc : 'env -> t -> t -> t * 'm
163162

164-
method constr : 'env -> constr -> constr * 'm
163+
method constr : 'env -> constr -> constr * 'm
165164

166-
method field : 'env -> field -> field * 'm
165+
method field : 'env -> field -> field * 'm
167166

168-
method list : 'env -> t -> t * 'm
167+
method list : 'env -> t -> t * 'm
169168

170-
method path : 'env -> Path.t -> t * 'm
169+
method path : 'env -> Path.t -> t * 'm
171170

172-
method optional : 'env -> t -> t * 'm
171+
method optional : 'env -> t -> t * 'm
173172

174-
method poly_variant : 'env -> constr list -> t * 'm
173+
method poly_variant : 'env -> constr list -> t * 'm
175174

176-
method prim : 'env -> prim -> t * 'm
175+
method prim : 'env -> prim -> t * 'm
177176

178-
method record : 'env -> field list -> decl * 'm
177+
method record : 'env -> field list -> decl * 'm
179178

180-
method t : 'env -> t -> t * 'm
179+
method t : 'env -> t -> t * 'm
181180

182-
method decl : 'env -> decl -> decl * 'm
181+
method decl : 'env -> decl -> decl * 'm
183182

184-
method tuple : 'env -> t list -> t * 'm
183+
method tuple : 'env -> t list -> t * 'm
185184

186-
method var : 'env -> string -> t * 'm
185+
method var : 'env -> string -> t * 'm
187186

188-
method variant : 'env -> constr list -> decl * 'm
189-
end
187+
method variant : 'env -> constr list -> decl * 'm
188+
end
190189
end
191190

192191
module Expr : sig

lsp/bin/typescript/ts_types.ml

Lines changed: 14 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -79,31 +79,29 @@ module type S = sig
7979

8080
val dyn_of_field : field -> Dyn.t
8181

82-
class map :
83-
object
84-
method typ : typ -> typ
82+
class map : object
83+
method typ : typ -> typ
8584

86-
method sum : typ list -> typ
85+
method sum : typ list -> typ
8786

88-
method interface : interface -> interface
87+
method interface : interface -> interface
8988

90-
method enum_anon : Enum.t -> Enum.t
89+
method enum_anon : Enum.t -> Enum.t
9190

92-
method field : field -> field
91+
method field : field -> field
9392

94-
method t : t -> t
95-
end
93+
method t : t -> t
94+
end
9695

97-
class ['a] fold :
98-
object
99-
method field : field -> init:'a -> 'a
96+
class ['a] fold : object
97+
method field : field -> init:'a -> 'a
10098

101-
method ident : ident -> init:'a -> 'a
99+
method ident : ident -> init:'a -> 'a
102100

103-
method t : t -> init:'a -> 'a
101+
method t : t -> init:'a -> 'a
104102

105-
method typ : typ -> init:'a -> 'a
106-
end
103+
method typ : typ -> init:'a -> 'a
104+
end
107105
end
108106

109107
module Make (Ident : sig

lsp/bin/typescript/ts_types.mli

Lines changed: 14 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -62,31 +62,29 @@ module type S = sig
6262

6363
val dyn_of_field : field -> Dyn.t
6464

65-
class map :
66-
object
67-
method enum_anon : Enum.t -> Enum.t
65+
class map : object
66+
method enum_anon : Enum.t -> Enum.t
6867

69-
method field : field -> field
68+
method field : field -> field
7069

71-
method interface : interface -> interface
70+
method interface : interface -> interface
7271

73-
method sum : typ list -> typ
72+
method sum : typ list -> typ
7473

75-
method t : t -> t
74+
method t : t -> t
7675

77-
method typ : typ -> typ
78-
end
76+
method typ : typ -> typ
77+
end
7978

80-
class ['a] fold :
81-
object
82-
method field : field -> init:'a -> 'a
79+
class ['a] fold : object
80+
method field : field -> init:'a -> 'a
8381

84-
method ident : ident -> init:'a -> 'a
82+
method ident : ident -> init:'a -> 'a
8583

86-
method t : t -> init:'a -> 'a
84+
method t : t -> init:'a -> 'a
8785

88-
method typ : typ -> init:'a -> 'a
89-
end
86+
method typ : typ -> init:'a -> 'a
87+
end
9088
end
9189

9290
module Unresolved : sig

lsp/src/diff.ml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -153,8 +153,9 @@ let edit ~from:orig ~to_:formatted : TextEdit.t list =
153153
text_edit
154154
~line
155155
(if prev_deleted_lines > 0 then
156-
Replace { deleted = prev_deleted_lines; added = added_lines }
157-
else Insert added_lines)
156+
Replace
157+
{ deleted = prev_deleted_lines; added = added_lines }
158+
else Insert added_lines)
158159
in
159160
(line + prev_deleted_lines, 0, edit :: edits_rev)
160161
| Equal { lines } ->

lsp/src/string_zipper.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -83,11 +83,11 @@ let cons sub list = if Substring.length sub = 0 then list else sub :: list
8383
let is_end t =
8484
let res = Substring.length t.current = t.rel_pos in
8585
(if res then
86-
match t.right with
87-
| [] -> ()
88-
| _ :: _ ->
89-
invalid_arg
90-
(sprintf "invalid state: current = %S" (Substring.to_string t.current)));
86+
match t.right with
87+
| [] -> ()
88+
| _ :: _ ->
89+
invalid_arg
90+
(sprintf "invalid state: current = %S" (Substring.to_string t.current)));
9191
res
9292

9393
let is_begin t =

0 commit comments

Comments
 (0)