Skip to content

Commit 1a63c65

Browse files
committed
Add in canonical paths for all Identifier types
1 parent 207d17c commit 1a63c65

File tree

17 files changed

+136
-33
lines changed

17 files changed

+136
-33
lines changed

src/document/comment.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -301,7 +301,8 @@ let heading_level_to_int = function
301301
| `Paragraph -> 4
302302
| `Subparagraph -> 5
303303

304-
let heading (attrs, { Odoc_model.Paths.iv = `Label (_, label); _ }, text) =
304+
let heading
305+
(attrs, { Odoc_model.Paths.Identifier.iv = `Label (_, label); _ }, text) =
305306
let label = Odoc_model.Names.LabelName.to_string label in
306307
let title = non_link_inline_element_list text in
307308
let level = heading_level_to_int attrs.Comment.heading_level in

src/document/url.ml

Lines changed: 12 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,13 @@ open Odoc_model.Names
44
module Root = Odoc_model.Root
55

66
let functor_arg_pos : Odoc_model.Paths.Identifier.FunctorParameter.t -> int =
7-
fun { Odoc_model.Paths.iv = `Parameter (p, _); _ } ->
8-
let rec inner_sig = function
9-
| `Result { Odoc_model.Paths.iv = p; _ } -> 1 + inner_sig p
10-
| `Module _ | `ModuleType _ | `Root _ | `Parameter _ -> 1
11-
in
12-
inner_sig p.Odoc_model.Paths.iv
7+
let open Odoc_model.Paths.Identifier in
8+
fun { iv = `Parameter (p, _); _ } ->
9+
let rec inner_sig = function
10+
| `Result { iv = p; _ } -> 1 + inner_sig p
11+
| `Module _ | `ModuleType _ | `Root _ | `Parameter _ -> 1
12+
in
13+
inner_sig p.iv
1314

1415
let render_path : Odoc_model.Paths.Path.t -> string =
1516
let open Odoc_model.Paths.Path in
@@ -90,7 +91,7 @@ module Path = struct
9091
| Identifier.Signature.t_pv
9192
| Identifier.ClassSignature.t_pv ]
9293

93-
and source = source_pv Odoc_model.Paths.id
94+
and source = source_pv Odoc_model.Paths.Identifier.id
9495

9596
type kind =
9697
[ `Module
@@ -179,7 +180,8 @@ module Path = struct
179180
| { iv = `Result p; _ } -> from_identifier (p :> source)
180181

181182
let from_identifier p =
182-
from_identifier (p : [< source_pv ] Odoc_model.Paths.id :> source)
183+
from_identifier
184+
(p : [< source_pv ] Odoc_model.Paths.Identifier.id :> source)
183185

184186
let to_list url =
185187
let rec loop acc { parent; name; kind } =
@@ -401,7 +403,8 @@ let from_path page =
401403
{ Anchor.page; anchor = ""; kind = (page.kind :> Anchor.kind) }
402404

403405
let from_identifier ~stop_before = function
404-
| { Odoc_model.Paths.iv = #Path.source_pv; _ } as p when not stop_before ->
406+
| { Odoc_model.Paths.Identifier.iv = #Path.source_pv; _ } as p
407+
when not stop_before ->
405408
Ok (from_path @@ Path.from_identifier p)
406409
| p -> Anchor.from_identifier p
407410

src/document/url.mli

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,9 @@ module Path : sig
3333
| Identifier.Signature.t_pv
3434
| Identifier.ClassSignature.t_pv ]
3535

36-
and source = source_pv Odoc_model.Paths.id
36+
and source = source_pv Odoc_model.Paths.Identifier.id
3737

38-
val from_identifier : [< source_pv ] Odoc_model.Paths.id -> t
38+
val from_identifier : [< source_pv ] Odoc_model.Paths.Identifier.id -> t
3939

4040
val to_list : t -> (kind * string) list
4141

src/model/paths.ml

Lines changed: 28 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,9 @@
1616

1717
open Names
1818

19-
type 'a id = 'a Paths_types.id = { iv : 'a; ihash : int; ikey : string }
20-
2119
module Identifier = struct
20+
type 'a id = 'a Paths_types.id = { iv : 'a; ihash : int; ikey : string }
21+
2222
type t = Paths_types.Identifier.any
2323

2424
type t_pv = Paths_types.Identifier.any_pv
@@ -157,6 +157,8 @@ module Identifier = struct
157157
module RootModule = struct
158158
type t = Paths_types.Identifier.root_module
159159

160+
type t_pv = Paths_types.Identifier.root_module_pv
161+
160162
let equal = equal
161163

162164
let hash = hash
@@ -191,6 +193,8 @@ module Identifier = struct
191193
module FunctorResult = struct
192194
type t = Paths_types.Identifier.functor_result
193195

196+
type t_pv = Paths_types.Identifier.functor_result_pv
197+
194198
let equal = equal
195199

196200
let hash = hash
@@ -225,6 +229,8 @@ module Identifier = struct
225229
module Constructor = struct
226230
type t = Paths_types.Identifier.constructor
227231

232+
type t_pv = Paths_types.Identifier.constructor_pv
233+
228234
let equal = equal
229235

230236
let hash = hash
@@ -235,6 +241,8 @@ module Identifier = struct
235241
module Field = struct
236242
type t = Paths_types.Identifier.field
237243

244+
type t_pv = Paths_types.Identifier.field_pv
245+
238246
let equal = equal
239247

240248
let hash = hash
@@ -245,6 +253,8 @@ module Identifier = struct
245253
module Extension = struct
246254
type t = Paths_types.Identifier.extension
247255

256+
type t_pv = Paths_types.Identifier.extension_pv
257+
248258
let equal = equal
249259

250260
let hash = hash
@@ -255,6 +265,8 @@ module Identifier = struct
255265
module Exception = struct
256266
type t = Paths_types.Identifier.exception_
257267

268+
type t_pv = Paths_types.Identifier.exception_pv
269+
258270
let equal = equal
259271

260272
let hash = hash
@@ -265,6 +277,8 @@ module Identifier = struct
265277
module Value = struct
266278
type t = Paths_types.Identifier.value
267279

280+
type t_pv = Paths_types.Identifier.value_pv
281+
268282
let equal = equal
269283

270284
let hash = hash
@@ -275,6 +289,8 @@ module Identifier = struct
275289
module Class = struct
276290
type t = Paths_types.Identifier.class_
277291

292+
type t_pv = Paths_types.Identifier.class_pv
293+
278294
let equal = equal
279295

280296
let hash = hash
@@ -285,6 +301,8 @@ module Identifier = struct
285301
module ClassType = struct
286302
type t = Paths_types.Identifier.class_type
287303

304+
type t_pv = Paths_types.Identifier.class_type_pv
305+
288306
let equal = equal
289307

290308
let hash = hash
@@ -295,6 +313,8 @@ module Identifier = struct
295313
module Method = struct
296314
type t = Paths_types.Identifier.method_
297315

316+
type t_pv = Paths_types.Identifier.method_pv
317+
298318
let equal = equal
299319

300320
let hash = hash
@@ -305,6 +325,8 @@ module Identifier = struct
305325
module InstanceVariable = struct
306326
type t = Paths_types.Identifier.instance_variable
307327

328+
type t_pv = Paths_types.Identifier.instance_variable_pv
329+
308330
let equal = equal
309331

310332
let hash = hash
@@ -339,6 +361,8 @@ module Identifier = struct
339361
module ContainerPage = struct
340362
type t = Paths_types.Identifier.container_page
341363

364+
type t_pv = Paths_types.Identifier.container_page_pv
365+
342366
let equal = equal
343367

344368
let hash = hash
@@ -349,6 +373,8 @@ module Identifier = struct
349373
module OdocId = struct
350374
type t = Paths_types.Identifier.odoc_id
351375

376+
type t_pv = Paths_types.Identifier.odoc_id_pv
377+
352378
let equal = equal
353379

354380
let hash = hash

src/model/paths.mli

Lines changed: 30 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,11 +16,11 @@
1616

1717
(** Identifiers for definitions *)
1818

19-
type 'a id = 'a Paths_types.id = { iv : 'a; ihash : int; ikey : string }
20-
2119
module Identifier : sig
2220
(** {2 Generic operations} *)
2321

22+
type 'a id = 'a Paths_types.id = { iv : 'a; ihash : int; ikey : string }
23+
2424
module Any : sig
2525
type t = Paths_types.Identifier.any
2626

@@ -94,6 +94,8 @@ module Identifier : sig
9494
module RootModule : sig
9595
type t = Paths_types.Identifier.root_module
9696

97+
type t_pv = Paths_types.Identifier.root_module_pv
98+
9799
val equal : t -> t -> bool
98100

99101
val hash : t -> int
@@ -128,6 +130,8 @@ module Identifier : sig
128130
module FunctorResult : sig
129131
type t = Paths_types.Identifier.functor_result
130132

133+
type t_pv = Paths_types.Identifier.functor_result_pv
134+
131135
val equal : t -> t -> bool
132136

133137
val hash : t -> int
@@ -162,6 +166,8 @@ module Identifier : sig
162166
module Constructor : sig
163167
type t = Paths_types.Identifier.constructor
164168

169+
type t_pv = Paths_types.Identifier.constructor_pv
170+
165171
val equal : t -> t -> bool
166172

167173
val hash : t -> int
@@ -172,6 +178,8 @@ module Identifier : sig
172178
module Field : sig
173179
type t = Paths_types.Identifier.field
174180

181+
type t_pv = Paths_types.Identifier.field_pv
182+
175183
val equal : t -> t -> bool
176184

177185
val hash : t -> int
@@ -182,6 +190,8 @@ module Identifier : sig
182190
module Extension : sig
183191
type t = Paths_types.Identifier.extension
184192

193+
type t_pv = Paths_types.Identifier.extension_pv
194+
185195
val equal : t -> t -> bool
186196

187197
val hash : t -> int
@@ -192,6 +202,8 @@ module Identifier : sig
192202
module Exception : sig
193203
type t = Paths_types.Identifier.exception_
194204

205+
type t_pv = Paths_types.Identifier.exception_pv
206+
195207
val equal : t -> t -> bool
196208

197209
val hash : t -> int
@@ -202,6 +214,8 @@ module Identifier : sig
202214
module Value : sig
203215
type t = Paths_types.Identifier.value
204216

217+
type t_pv = Paths_types.Identifier.value_pv
218+
205219
val equal : t -> t -> bool
206220

207221
val hash : t -> int
@@ -212,6 +226,8 @@ module Identifier : sig
212226
module Class : sig
213227
type t = Paths_types.Identifier.class_
214228

229+
type t_pv = Paths_types.Identifier.class_pv
230+
215231
val equal : t -> t -> bool
216232

217233
val hash : t -> int
@@ -222,6 +238,8 @@ module Identifier : sig
222238
module ClassType : sig
223239
type t = Paths_types.Identifier.class_type
224240

241+
type t_pv = Paths_types.Identifier.class_type_pv
242+
225243
val equal : t -> t -> bool
226244

227245
val hash : t -> int
@@ -232,6 +250,8 @@ module Identifier : sig
232250
module Method : sig
233251
type t = Paths_types.Identifier.method_
234252

253+
type t_pv = Paths_types.Identifier.method_pv
254+
235255
val equal : t -> t -> bool
236256

237257
val hash : t -> int
@@ -242,6 +262,8 @@ module Identifier : sig
242262
module InstanceVariable : sig
243263
type t = Paths_types.Identifier.instance_variable
244264

265+
type t_pv = Paths_types.Identifier.instance_variable_pv
266+
245267
val equal : t -> t -> bool
246268

247269
val hash : t -> int
@@ -276,6 +298,8 @@ module Identifier : sig
276298
module ContainerPage : sig
277299
type t = Paths_types.Identifier.container_page
278300

301+
type t_pv = Paths_types.Identifier.container_page_pv
302+
279303
val equal : t -> t -> bool
280304

281305
val hash : t -> int
@@ -286,6 +310,8 @@ module Identifier : sig
286310
module OdocId : sig
287311
type t = Paths_types.Identifier.odoc_id
288312

313+
type t_pv = Paths_types.Identifier.odoc_id_pv
314+
289315
val equal : t -> t -> bool
290316

291317
val hash : t -> int
@@ -343,10 +369,10 @@ module Identifier : sig
343369
type t = Paths_types.Identifier.path_any
344370
end
345371

346-
type t = Paths_types.Identifier.any
347-
348372
type t_pv = Paths_types.Identifier.any_pv
349373

374+
type t = Paths_types.Identifier.any
375+
350376
val hash : t -> int
351377

352378
val name : [< t_pv ] id -> string

0 commit comments

Comments
 (0)