Skip to content

Commit 99333b9

Browse files
committed
Preview: Upgrade to OCamlformat 0.27.0-preview1 (unreleased)
The aim of this preview is to gather feedback. Changelog can be found here: https://github.com/ocaml-ppx/ocamlformat/blob/main/CHANGES.md
1 parent c0f4c89 commit 99333b9

Some content is hidden

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

65 files changed

+597
-600
lines changed

.ocamlformat

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
11
module-item-spacing=preserve
2-
version=0.26.1
2+
version=0.27.0-preview1
33
ocaml-version=4.02

doc/examples/expansion.mli

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
(** Examples of different features of Expansion *)
22

3-
(** For details on what each of the following examples is showing,
4-
see the explanations in the {{!page-features}Features page} *)
3+
(** For details on what each of the following examples is showing, see the
4+
explanations in the {{!page-features} Features page} *)
55

66
[@@@warning "-67"]
77
module Simple : sig
@@ -23,7 +23,8 @@ module Aliases : sig
2323
end
2424

2525
module ModuleTypeAliases : sig
26-
(** Demonstrates that module types are not expanded if they're a simple path to another. *)
26+
(** Demonstrates that module types are not expanded if they're a simple path
27+
to another. *)
2728

2829
module type A = sig
2930
type t
@@ -125,7 +126,8 @@ module DeepEquality : sig
125126
end
126127

127128
module DeepEquality2 : sig
128-
(** Demonstrates expansion involving an equation on a type in a submodule, but the submodule is already a simple signature *)
129+
(** Demonstrates expansion involving an equation on a type in a submodule, but
130+
the submodule is already a simple signature *)
129131

130132
module type MODTYPE = sig
131133
module X : sig
@@ -172,7 +174,8 @@ module ModuleTypeOf : sig
172174
end
173175

174176
module ModuleTypeOfComplications : sig
175-
(** Demonstrates the interaction of [module type of] and destructive module substitution *)
177+
(** Demonstrates the interaction of [module type of] and destructive module
178+
substitution *)
176179

177180
module type S = sig
178181
module X : sig

doc/examples/markup.mli

Lines changed: 48 additions & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -1,42 +1,41 @@
11
(** Markup examples. *)
22

33
(** The OCaml manual gives a
4-
{{:https://ocaml.org/manual/ocamldoc.html#ss:ocamldoc-placement}comprehensive example}
5-
of comment placement. This has been replicated in the module Foo below to
6-
show how this is rendered by [odoc]. *)
4+
{{:https://ocaml.org/manual/ocamldoc.html#ss:ocamldoc-placement}
5+
comprehensive example} of comment placement. This has been replicated in
6+
the module Foo below to show how this is rendered by [odoc]. *)
77

88
module type Foo = sig
9-
(** The first special comment of the file is the comment associated
10-
with the whole module.*)
9+
(** The first special comment of the file is the comment associated with the
10+
whole module.*)
1111

12-
(** Special comments can be placed between elements and are kept
13-
by the OCamldoc tool, but are not associated to any element.
14-
[@]-tags in these comments are ignored.*)
12+
(** Special comments can be placed between elements and are kept by the
13+
OCamldoc tool, but are not associated to any element. [@]-tags in these
14+
comments are ignored.*)
1515

1616
(*******************************************************************)
17-
(** Comments like the one above, with more than two asterisks,
18-
are ignored. *)
17+
(** Comments like the one above, with more than two asterisks, are ignored. *)
1918

2019
(** The comment for function f. *)
2120
val f : int -> int -> int
2221
(** The continuation of the comment for function f. *)
2322

2423
(* Hello, I'm a simple comment :-) *)
2524
exception My_exception of (int -> int) * int
26-
(** Comment for exception My_exception, even with a simple comment
27-
between the special comment and the exception.*)
25+
(** Comment for exception My_exception, even with a simple comment between the
26+
special comment and the exception.*)
2827

29-
(** Comment for type weather *)
28+
(** Comment for type weather *)
3029
type weather =
3130
| Rain of int (** The comment for constructor Rain *)
3231
| Sun (** The comment for constructor Sun *)
3332

34-
(** Comment for type weather2 *)
33+
(** Comment for type weather2 *)
3534
type weather2 =
3635
| Rain of int (** The comment for constructor Rain *)
3736
| Sun (** The comment for constructor Sun *)
38-
(** I can continue the comment for type weather2 here
39-
because there is already a comment associated to the last constructor.*)
37+
(** I can continue the comment for type weather2 here because there is already
38+
a comment associated to the last constructor.*)
4039

4140
(** The comment for type my_record *)
4241
type my_record = {
@@ -67,9 +66,8 @@ module type Foo = sig
6766
val toto : int
6867
(** The comment for attribute toto. *)
6968

70-
(** This comment is not attached to titi since
71-
there is a blank line before titi, but is kept
72-
as a comment in the class. *)
69+
(** This comment is not attached to titi since there is a blank line before
70+
titi, but is kept as a comment in the class. *)
7371

7472
val titi : string
7573

@@ -126,8 +124,8 @@ module Stop : sig
126124
end
127125

128126
val foo : string
129-
(** This value appears in the documentation, since the Stop special comment
130-
in the class does not affect the parent module of the class.*)
127+
(** This value appears in the documentation, since the Stop special comment in
128+
the class does not affect the parent module of the class.*)
131129

132130
(**/**)
133131

@@ -137,14 +135,14 @@ module Stop : sig
137135
(**/**)
138136

139137
type t = string
140-
(** The type t appears since in the documentation since the previous stop comment
141-
toggled off the "no documentation mode". *)
138+
(** The type t appears since in the documentation since the previous stop
139+
comment toggled off the "no documentation mode". *)
142140
end
143141

144142
(** {2 Scoping rules} *)
145143
module Scope : sig
146-
(** In this floating comment I can refer to type {!t} and value {!v}
147-
declared later in the signature *)
144+
(** In this floating comment I can refer to type {!t} and value {!v} declared
145+
later in the signature *)
148146

149147
type t
150148

@@ -155,12 +153,12 @@ module Scope : sig
155153
val y : int
156154

157155
module A : sig
158-
(** In this module I can refer to val {!x} declared above as well as
159-
type {!u} declared later in the parent module. Elements declared
160-
in this signature take priority, so {!y} refers to {!A.y} as
161-
opposed to the [y] declared in the parent signature.
162-
163-
@see 'markup.mli' for a good time *)
156+
(** In this module I can refer to val {!x} declared above as well as type
157+
{!u} declared later in the parent module. Elements declared in this
158+
signature take priority, so {!y} refers to {!A.y} as opposed to the [y]
159+
declared in the parent signature.
160+
161+
@see 'markup.mli' for a good time *)
164162

165163
val y : string
166164
end
@@ -174,25 +172,27 @@ module Preamble_examples : sig
174172
(** This is the comment attached to the declaration of Hidden__Module *)
175173
module Hidden__Module : sig
176174
(** This is the top comment declared in the module Hidden__module.
177-
178-
This is the second paragraph in the module Hidden__module.
179-
180-
@canonical Odoc_examples.Markup.Module *)
175+
176+
This is the second paragraph in the module Hidden__module.
177+
178+
@canonical Odoc_examples.Markup.Module *)
181179

182180
type t
183181
(** This is a comment on type t *)
184182
end
185183

186184
module Module = Hidden__Module
187-
(** This comment is on the declaration of Module as an alias of Hidden__Module *)
185+
(** This comment is on the declaration of Module as an alias of Hidden__Module
186+
*)
188187

189-
(** This is the comment attached to the declaration of module Hidden__Module2 *)
188+
(** This is the comment attached to the declaration of module Hidden__Module2
189+
*)
190190
module Hidden__Module2 : sig
191191
(** This is the top comment declared in the module Hidden__module2.
192-
193-
This is the second paragraph in the module Hidden__module2.
194-
195-
@canonical Odoc_examples.Markup.Module2 *)
192+
193+
This is the second paragraph in the module Hidden__module2.
194+
195+
@canonical Odoc_examples.Markup.Module2 *)
196196

197197
type t
198198
(** This is a comment on type t *)
@@ -202,23 +202,22 @@ module Preamble_examples : sig
202202

203203
module Nonhidden_module : sig
204204
(** This is the top comment declared in the module Hidden__module2.
205-
206-
This is the second paragraph in the module Hidden__module2.
207-
*)
205+
206+
This is the second paragraph in the module Hidden__module2. *)
208207
end
209208

210209
module Module3 = Nonhidden_module
211-
(** This comment is on the declaration of Module3 as an alias of Nonhidden_module *)
210+
(** This comment is on the declaration of Module3 as an alias of
211+
Nonhidden_module *)
212212

213213
module Nonhidden_module2 : sig
214214
(** This is the top comment declared in the module Hidden__module2.
215-
216-
This is the second paragraph in the module Hidden__module2.
217-
*)
215+
216+
This is the second paragraph in the module Hidden__module2. *)
218217
end
219218

220219
module Module4 = Nonhidden_module2
221220

222221
(** The [modules] special reference can be used to refer to a list of modules.
223-
It uses the synopsis from the modules *)
222+
It uses the synopsis from the modules *)
224223
end

doc/examples/odoc_examples.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
(** Examples of the output from [odoc] *)
22

3-
(** These examples are intended to be viewed alongside the
4-
source code. See {:https://github.com/ocaml/odoc/tree/master/doc/examples} *)
3+
(** These examples are intended to be viewed alongside the source code. See
4+
{:https://github.com/ocaml/odoc/tree/master/doc/examples} *)
55

66
module Expansion = Expansion
77
module Resolution = Resolution

doc/examples/resolution.mli

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
11
(** Examples of Path, Fragment and Reference Resolution *)
22

3-
(** This module contains examples of some of the features of Resolution
4-
as described in the page {!page-features}. See the explanations there for
5-
details on what each of these demonstrates. *)
3+
(** This module contains examples of some of the features of Resolution as
4+
described in the page {!page-features}. See the explanations there for
5+
details on what each of these demonstrates. *)
66

77
[@@@warning "-67"]
88

@@ -28,7 +28,7 @@ end
2828

2929
module HiddenAlias : sig
3030
(** Demonstrates a reference to an item in a module that's an alias of a
31-
hidden module. *)
31+
hidden module. *)
3232

3333
(**/**)
3434

@@ -110,8 +110,9 @@ module References : sig
110110
end
111111
end
112112

113-
(** We can refer unambiguously to {!module-type-A.t} in module type [A] or {!module-A.t} in module [A],
114-
and also where there are name clashes within the path: {!module-A.module-B.t} or {!module-A.module-type-B.t} *)
113+
(** We can refer unambiguously to {!module-type-A.t} in module type [A] or
114+
{!module-A.t} in module [A], and also where there are name clashes within
115+
the path: {!module-A.module-B.t} or {!module-A.module-type-B.t} *)
115116
end
116117

117118
module Complicated_1 : sig

src/document/comment.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,9 @@ module Reference = struct
117117
| Some s -> s
118118
and tooltip =
119119
(* Add a tooltip if the content is not the rendered reference. *)
120-
match text with None -> None | Some _ -> Some rendered
120+
match text with
121+
| None -> None
122+
| Some _ -> Some rendered
121123
in
122124
match Url.from_identifier ~stop_before:false id with
123125
| Ok url ->

src/document/doctree.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -196,8 +196,8 @@ end
196196
module Headings : sig
197197
val fold :
198198
enter_subpages:bool -> ('a -> Heading.t -> 'a) -> 'a -> Page.t -> 'a
199-
(** Fold over every headings, follow nested documentedsrc and
200-
expansions, as well as subpages if [enter_subpages] is [true]. *)
199+
(** Fold over every headings, follow nested documentedsrc and expansions, as
200+
well as subpages if [enter_subpages] is [true]. *)
201201

202202
val foldmap :
203203
enter_subpages:bool ->

src/document/generator.ml

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -767,10 +767,10 @@ module Make (Syntax : SYNTAX) = struct
767767
intro @ variants @ ending
768768

769769
let format_params :
770-
'row.
771-
?delim:[ `parens | `brackets ] ->
772-
Odoc_model.Lang.TypeDecl.param list ->
773-
text =
770+
'row.
771+
?delim:[ `parens | `brackets ] ->
772+
Odoc_model.Lang.TypeDecl.param list ->
773+
text =
774774
fun ?(delim = `parens) params ->
775775
let format_param { Odoc_model.Lang.TypeDecl.desc; variance; injectivity }
776776
=
@@ -808,11 +808,11 @@ module Make (Syntax : SYNTAX) = struct
808808
++ O.box_hv_no_indent (type_expr t2)))
809809

810810
let format_manifest :
811-
'inner_row 'outer_row.
812-
?is_substitution:bool ->
813-
?compact_variants:bool ->
814-
Odoc_model.Lang.TypeDecl.Equation.t ->
815-
text * bool =
811+
'inner_row 'outer_row.
812+
?is_substitution:bool ->
813+
?compact_variants:bool ->
814+
Odoc_model.Lang.TypeDecl.Equation.t ->
815+
text * bool =
816816
fun ?(is_substitution = false) ?(compact_variants = true) equation ->
817817
let _ = compact_variants in
818818
(* TODO *)

src/document/generator_signatures.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,7 @@ type rendered_item = DocumentedSrc.t
55

66
type text = Codefmt.t
77

8-
(** HTML generation syntax customization module. See {!ML} and
9-
{!Reason}. *)
8+
(** HTML generation syntax customization module. See {!ML} and {!Reason}. *)
109
module type SYNTAX = sig
1110
module Obj : sig
1211
val close_tag_closed : string

src/document/targets.mli

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,7 @@
1-
(** Collect all the urls of pages defined by a model.
2-
3-
Roughly a simplified version of the normal process
4-
to convert a model into a document, only for extracting Urls.
5-
Used to determine the build targets.
6-
*)
1+
(** Collect all the urls of pages defined by a model.
2+
3+
Roughly a simplified version of the normal process to convert a model into a
4+
document, only for extracting Urls. Used to determine the build targets. *)
75

86
open Odoc_model.Lang
97

0 commit comments

Comments
 (0)