• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

ocaml / odoc / 2072

10 Jun 2024 10:09AM UTC coverage: 71.986% (+0.2%) from 71.774%
2072

Pull #1145

github

web-flow
Merge 1b7b0910b into 1ced6f23f
Pull Request #1145: "Global" Sidebar

195 of 220 new or added lines in 12 files covered. (88.64%)

630 existing lines in 13 files now uncovered.

9834 of 13661 relevant lines covered (71.99%)

3561.61 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

78.48
/src/document/url.ml
1
open Result
2
open Odoc_model.Paths
3
open Odoc_model.Names
4
module Root = Odoc_model.Root
5

6
let render_path : Odoc_model.Paths.Path.t -> string =
7
  let open Odoc_model.Paths.Path in
8
  let rec render_resolved : Odoc_model.Paths.Path.Resolved.t -> string =
9
    let open Resolved in
10
    function
11
    | `Identifier id -> Identifier.name id
4,542✔
12
    | `OpaqueModule p -> render_resolved (p :> t)
6✔
13
    | `OpaqueModuleType p -> render_resolved (p :> t)
150✔
14
    | `Subst (_, p) -> render_resolved (p :> t)
18✔
15
    | `SubstT (_, p) -> render_resolved (p :> t)
24✔
16
    | `Alias (dest, `Resolved src) ->
×
17
        if Odoc_model.Paths.Path.Resolved.(is_hidden (src :> t)) then
×
18
          render_resolved (dest :> t)
×
UNCOV
19
        else render_resolved (src :> t)
×
20
    | `Alias (dest, src) ->
140✔
21
        if Odoc_model.Paths.Path.is_hidden (src :> Path.t) then
UNCOV
22
          render_resolved (dest :> t)
×
23
        else render_path (src :> Path.t)
140✔
24
    | `AliasModuleType (p1, p2) ->
102✔
25
        if Odoc_model.Paths.Path.Resolved.(is_hidden (p2 :> t)) then
102✔
UNCOV
26
          render_resolved (p1 :> t)
×
27
        else render_resolved (p2 :> t)
102✔
28
    | `Hidden p -> render_resolved (p :> t)
48✔
29
    | `Module (p, s) -> render_resolved (p :> t) ^ "." ^ ModuleName.to_string s
186✔
30
    | `Canonical (_, `Resolved p) -> render_resolved (p :> t)
89✔
31
    | `Canonical (p, _) -> render_resolved (p :> t)
×
32
    | `CanonicalModuleType (_, `Resolved p) -> render_resolved (p :> t)
×
UNCOV
33
    | `CanonicalModuleType (p, _) -> render_resolved (p :> t)
×
34
    | `CanonicalType (_, `Resolved p) -> render_resolved (p :> t)
3✔
UNCOV
35
    | `CanonicalType (p, _) -> render_resolved (p :> t)
×
36
    | `Substituted c -> render_resolved (c :> t)
24✔
37
    | `SubstitutedMT c -> render_resolved (c :> t)
×
38
    | `SubstitutedT c -> render_resolved (c :> t)
×
UNCOV
39
    | `SubstitutedCT c -> render_resolved (c :> t)
×
40
    | `Apply (rp, p) ->
54✔
41
        render_resolved (rp :> t)
54✔
42
        ^ "("
43
        ^ render_resolved (p :> Odoc_model.Paths.Path.Resolved.t)
54✔
44
        ^ ")"
45
    | `ModuleType (p, s) ->
182✔
46
        render_resolved (p :> t) ^ "." ^ ModuleTypeName.to_string s
182✔
47
    | `Type (p, s) -> render_resolved (p :> t) ^ "." ^ TypeName.to_string s
445✔
UNCOV
48
    | `Value (p, s) -> render_resolved (p :> t) ^ "." ^ ValueName.to_string s
×
49
    | `Class (p, s) -> render_resolved (p :> t) ^ "." ^ ClassName.to_string s
12✔
50
    | `ClassType (p, s) ->
×
UNCOV
51
        render_resolved (p :> t) ^ "." ^ ClassTypeName.to_string s
×
52
  and render_path : Odoc_model.Paths.Path.t -> string =
53
   fun x ->
54
    match x with
4,876✔
55
    | `Identifier (id, _) -> Identifier.name id
152✔
56
    | `Root root -> root
×
UNCOV
57
    | `Forward root -> root
×
58
    | `Dot (prefix, suffix) -> render_path (prefix :> t) ^ "." ^ suffix
84✔
59
    | `Apply (p1, p2) ->
12✔
60
        render_path (p1 :> t) ^ "(" ^ render_path (p2 :> t) ^ ")"
12✔
61
    | `Resolved rp -> render_resolved rp
4,628✔
62
    | `Substituted m -> render_path (m :> t)
×
63
    | `SubstitutedMT m -> render_path (m :> t)
×
64
    | `SubstitutedT m -> render_path (m :> t)
×
UNCOV
65
    | `SubstitutedCT m -> render_path (m :> t)
×
66
  in
67

68
  render_path
69

70
module Error = struct
71
  type nonrec t =
72
    | Not_linkable of string
73
    | Uncaught_exn of string
74
    (* These should basicaly never happen *)
75
    | Unexpected_anchor of string
76

77
  let to_string = function
78
    | Not_linkable s -> Printf.sprintf "Not_linkable %S" s
×
79
    | Uncaught_exn s -> Printf.sprintf "Uncaught_exn %S" s
×
UNCOV
80
    | Unexpected_anchor s -> Printf.sprintf "Unexpected_anchor %S" s
×
81
end
82

UNCOV
83
let ( >>= ) x f = match x with Ok x -> f x | Error _ as e -> e
×
84

85
module Path = struct
86
  type nonsrc_pv =
87
    [ Identifier.Page.t_pv
88
    | Identifier.Signature.t_pv
89
    | Identifier.ClassSignature.t_pv ]
90

91
  type any_pv =
92
    [ nonsrc_pv
93
    | Identifier.SourcePage.t_pv
94
    | Identifier.SourceDir.t_pv
95
    | Identifier.AssetFile.t_pv ]
96

97
  and any = any_pv Odoc_model.Paths.Identifier.id
98

99
  type kind =
100
    [ `Module
101
    | `Page
102
    | `LeafPage
103
    | `ModuleType
104
    | `Parameter of int
105
    | `Class
106
    | `ClassType
107
    | `File
108
    | `SourcePage ]
109

110
  let string_of_kind : kind -> string = function
111
    | `Page -> "page"
16✔
112
    | `Module -> "module"
7,564✔
113
    | `LeafPage -> "leaf-page"
5✔
114
    | `ModuleType -> "module-type"
7,255✔
115
    | `Parameter arg_num -> Printf.sprintf "argument-%d" arg_num
1,489✔
116
    | `Class -> "class"
601✔
117
    | `ClassType -> "class-type"
219✔
UNCOV
118
    | `File -> "file"
×
119
    | `SourcePage -> "source"
2✔
120

121
  let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind)
14,078✔
122

123
  type t = { kind : kind; parent : t option; name : string }
124

125
  let mk ?parent kind name = { kind; parent; name }
31,324✔
126

127
  let rec from_identifier : any -> t =
128
   fun x ->
129
    match x with
31,846✔
130
    | { iv = `Root (parent, unit_name); _ } ->
13,603✔
131
        let parent =
132
          match parent with
133
          | Some p -> Some (from_identifier (p :> any))
286✔
134
          | None -> None
13,317✔
135
        in
136
        let kind = `Module in
137
        let name = ModuleName.to_string unit_name in
138
        mk ?parent kind name
13,603✔
139
    | { iv = `Page (parent, page_name); _ } ->
596✔
140
        let parent =
141
          match parent with
142
          | Some p -> Some (from_identifier (p :> any))
90✔
143
          | None -> None
506✔
144
        in
145
        let kind = `Page in
146
        let name = PageName.to_string page_name in
147
        mk ?parent kind name
596✔
148
    | { iv = `LeafPage (parent, page_name); _ } ->
46✔
149
        let parent =
150
          match parent with
151
          | Some p -> Some (from_identifier (p :> any))
38✔
152
          | None -> None
8✔
153
        in
154
        let kind = `LeafPage in
155
        let name = PageName.to_string page_name in
156
        mk ?parent kind name
46✔
157
    | { iv = `Module (parent, mod_name); _ } ->
8,990✔
158
        let parent = from_identifier (parent :> any) in
159
        let kind = `Module in
8,990✔
160
        let name = ModuleName.to_string mod_name in
161
        mk ~parent kind name
8,990✔
162
    | { iv = `Parameter (functor_id, arg_name); _ } as p ->
1,627✔
163
        let parent = from_identifier (functor_id :> any) in
164
        let arg_num = Identifier.FunctorParameter.functor_arg_pos p in
1,627✔
165
        let kind = `Parameter arg_num in
1,627✔
166
        let name = ModuleName.to_string arg_name in
167
        mk ~parent kind name
1,627✔
168
    | { iv = `ModuleType (parent, modt_name); _ } ->
5,822✔
169
        let parent = from_identifier (parent :> any) in
170
        let kind = `ModuleType in
5,822✔
171
        let name = ModuleTypeName.to_string modt_name in
172
        mk ~parent kind name
5,822✔
173
    | { iv = `Class (parent, name); _ } ->
372✔
174
        let parent = from_identifier (parent :> any) in
175
        let kind = `Class in
372✔
176
        let name = ClassName.to_string name in
177
        mk ~parent kind name
372✔
178
    | { iv = `ClassType (parent, name); _ } ->
130✔
179
        let parent = from_identifier (parent :> any) in
180
        let kind = `ClassType in
130✔
181
        let name = ClassTypeName.to_string name in
182
        mk ~parent kind name
130✔
183
    | { iv = `Result p; _ } -> from_identifier (p :> any)
522✔
UNCOV
184
    | { iv = `SourceDir (parent, name); _ } ->
×
185
        let parent = from_identifier (parent :> any) in
UNCOV
186
        let kind = `Page in
×
187
        mk ~parent kind name
188
    | { iv = `SourcePage (parent, name); _ } ->
136✔
189
        let parent = from_identifier (parent :> any) in
190
        let kind = `SourcePage in
136✔
191
        mk ~parent kind name
192
    | { iv = `AssetFile (parent, name); _ } ->
2✔
193
        let parent = from_identifier (parent :> any) in
194
        let kind = `File in
2✔
195
        mk ~parent kind name
196

197
  let from_identifier p =
198
    from_identifier (p : [< any_pv ] Odoc_model.Paths.Identifier.id :> any)
13,831✔
199

200
  let to_list url =
201
    let rec loop acc { parent; name; kind } =
17,936✔
202
      match parent with
38,782✔
203
      | None -> (kind, name) :: acc
17,936✔
204
      | Some p -> loop ((kind, name) :: acc) p
20,846✔
205
    in
206
    loop [] url
207

208
  let of_list l =
209
    let rec inner parent = function
2,512✔
210
      | [] -> parent
2,512✔
211
      | (kind, name) :: xs -> inner (Some { parent; name; kind }) xs
4,887✔
212
    in
213
    inner None l
214

215
  let split :
216
      is_dir:(kind -> [ `Always | `Never | `IfNotLast ]) ->
217
      (kind * string) list ->
218
      (kind * string) list * (kind * string) list =
219
   fun ~is_dir l ->
220
    let rec inner dirs = function
15,759✔
221
      | [ ((kind, _) as x) ] when is_dir kind = `IfNotLast ->
7,451✔
222
          (List.rev dirs, [ x ])
4✔
223
      | ((kind, _) as x) :: xs when is_dir kind <> `Never ->
18,636✔
224
          inner (x :: dirs) xs
5,252✔
225
      | xs -> (List.rev dirs, xs)
15,755✔
226
    in
227
    inner [] l
228
end
229

230
module Anchor = struct
231
  type kind =
232
    [ Path.kind
233
    | `Section
234
    | `Type
235
    | `Extension
236
    | `ExtensionDecl
237
    | `Exception
238
    | `Method
239
    | `Val
240
    | `Constructor
241
    | `Field
242
    | `SourceAnchor ]
243

244
  let string_of_kind : kind -> string = function
245
    | #Path.kind as k -> Path.string_of_kind k
66✔
UNCOV
246
    | `Section -> "section"
×
247
    | `Type -> "type"
4,938✔
248
    | `Extension -> "extension"
489✔
249
    | `ExtensionDecl -> "extension-decl"
99✔
250
    | `Exception -> "exception"
176✔
251
    | `Method -> "method"
66✔
252
    | `Val -> "val"
809✔
253
    | `Constructor -> "constructor"
909✔
254
    | `Field -> "field"
120✔
UNCOV
255
    | `SourceAnchor -> "source-anchor"
×
256

257
  let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind)
6,213✔
258

259
  type t = { page : Path.t; anchor : string; kind : kind }
260

261
  let anchorify_path { Path.parent; name; kind } =
262
    match parent with
1,530✔
263
    | None -> assert false (* We got a root, should never happen *)
264
    | Some page ->
1,530✔
265
        let anchor = Printf.sprintf "%s-%s" (Path.string_of_kind kind) name in
1,530✔
266
        { page; anchor; kind = (kind :> kind) }
1,530✔
267

268
  let add_suffix ~kind { page; anchor; _ } suffix =
269
    { page; anchor = anchor ^ "." ^ suffix; kind }
1,055✔
270

271
  let mk ~kind parent str_name =
272
    let page = Path.from_identifier parent in
192✔
273
    Ok { page; anchor = str_name; kind }
192✔
274

275
  let rec from_identifier : Identifier.t -> (t, Error.t) result =
276
    let open Error in
277
    function
278
    | { iv = `Module (parent, mod_name); _ } ->
1,458✔
279
        let parent = Path.from_identifier (parent :> Path.any) in
280
        let kind = `Module in
1,458✔
281
        let anchor =
282
          Printf.sprintf "%s-%s" (Path.string_of_kind kind)
1,458✔
283
            (ModuleName.to_string mod_name)
1,458✔
284
        in
285
        Ok { page = parent; anchor; kind }
1,458✔
286
    | { iv = `Root _; _ } as p ->
8✔
287
        let page = Path.from_identifier (p :> Path.any) in
288
        Ok { page; kind = `Module; anchor = "" }
8✔
UNCOV
289
    | { iv = `Page _; _ } as p ->
×
290
        let page = Path.from_identifier (p :> Path.any) in
291
        Ok { page; kind = `Page; anchor = "" }
×
UNCOV
292
    | { iv = `LeafPage _; _ } as p ->
×
293
        let page = Path.from_identifier (p :> Path.any) in
UNCOV
294
        Ok { page; kind = `LeafPage; anchor = "" }
×
295
    (* For all these identifiers, page names and anchors are the same *)
296
    | {
UNCOV
297
        iv = `Parameter _ | `Result _ | `ModuleType _ | `Class _ | `ClassType _;
×
298
        _;
299
      } as p ->
300
        Ok (anchorify_path @@ Path.from_identifier p)
1,530✔
301
    | { iv = `Type (parent, type_name); _ } ->
4,900✔
302
        let page = Path.from_identifier (parent :> Path.any) in
303
        let kind = `Type in
4,900✔
304
        Ok
305
          {
306
            page;
307
            anchor =
308
              Format.asprintf "%a-%s" pp_kind kind
4,900✔
309
                (TypeName.to_string type_name);
4,900✔
310
            kind;
311
          }
312
    | { iv = `CoreType ty_name; _ } ->
1,954✔
313
        Error (Not_linkable ("core_type:" ^ TypeName.to_string ty_name))
1,954✔
314
    | { iv = `Extension (parent, name); _ } ->
252✔
315
        let page = Path.from_identifier (parent :> Path.any) in
316
        let kind = `Extension in
252✔
317
        Ok
318
          {
319
            page;
320
            anchor =
321
              Format.asprintf "%a-%s" pp_kind kind
252✔
322
                (ExtensionName.to_string name);
252✔
323
            kind;
324
          }
325
    | { iv = `ExtensionDecl (parent, name, _); _ } ->
4✔
326
        let page = Path.from_identifier (parent :> Path.any) in
327
        let kind = `ExtensionDecl in
4✔
328
        Ok
329
          {
330
            page;
331
            anchor =
332
              Format.asprintf "%a-%s" pp_kind kind
4✔
333
                (ExtensionName.to_string name);
4✔
334
            kind;
335
          }
336
    | { iv = `Exception (parent, name); _ } ->
124✔
337
        let page = Path.from_identifier (parent :> Path.any) in
338
        let kind = `Exception in
124✔
339
        Ok
340
          {
341
            page;
342
            anchor =
343
              Format.asprintf "%a-%s" pp_kind kind
124✔
344
                (ExceptionName.to_string name);
124✔
345
            kind;
346
          }
347
    | { iv = `CoreException name; _ } ->
×
UNCOV
348
        Error (Not_linkable ("core_exception:" ^ ExceptionName.to_string name))
×
349
    | { iv = `Value (parent, name); _ } ->
760✔
350
        let page = Path.from_identifier (parent :> Path.any) in
351
        let kind = `Val in
760✔
352
        Ok
353
          {
354
            page;
355
            anchor =
356
              Format.asprintf "%a-%s" pp_kind kind (ValueName.to_string name);
760✔
357
            kind;
358
          }
359
    | { iv = `Method (parent, name); _ } ->
66✔
360
        let str_name = MethodName.to_string name in
361
        let page = Path.from_identifier (parent :> Path.any) in
66✔
362
        let kind = `Method in
66✔
363
        Ok
364
          { page; anchor = Format.asprintf "%a-%s" pp_kind kind str_name; kind }
66✔
365
    | { iv = `InstanceVariable (parent, name); _ } ->
12✔
366
        let str_name = InstanceVariableName.to_string name in
367
        let page = Path.from_identifier (parent :> Path.any) in
12✔
368
        let kind = `Val in
12✔
369
        Ok
370
          { page; anchor = Format.asprintf "%a-%s" pp_kind kind str_name; kind }
12✔
371
    | { iv = `Constructor (parent, name); _ } ->
783✔
372
        from_identifier (parent :> Identifier.t) >>= fun page ->
783✔
373
        let kind = `Constructor in
783✔
374
        let suffix = ConstructorName.to_string name in
375
        Ok (add_suffix ~kind page suffix)
783✔
376
    | { iv = `Field (parent, name); _ } ->
120✔
377
        from_identifier (parent :> Identifier.t) >>= fun page ->
120✔
378
        let kind = `Field in
120✔
379
        let suffix = FieldName.to_string name in
380
        Ok (add_suffix ~kind page suffix)
120✔
381
    | { iv = `Label (parent, anchor); _ } -> (
192✔
382
        let str_name = LabelName.to_string anchor in
383
        (* [Identifier.LabelParent.t] contains datatypes. [`CoreType] can't
384
           happen, [`Type] may not happen either but just in case, use the
385
           grand-parent. *)
386
        match parent with
192✔
UNCOV
387
        | { iv = `CoreType _; _ } ->
×
388
            Error (Unexpected_anchor "core_type label parent")
UNCOV
389
        | { iv = `Type (gp, _); _ } -> mk ~kind:`Section gp str_name
×
390
        | { iv = #Path.nonsrc_pv; _ } as p ->
192✔
391
            mk ~kind:`Section (p :> Path.any) str_name)
392
    | { iv = `SourceLocation (parent, loc); _ } ->
70✔
393
        let page = Path.from_identifier (parent :> Path.any) in
394
        Ok { page; kind = `SourceAnchor; anchor = DefName.to_string loc }
70✔
395
    | { iv = `SourceLocationInternal (parent, loc); _ } ->
3✔
396
        let page = Path.from_identifier (parent :> Path.any) in
397
        Ok { page; kind = `SourceAnchor; anchor = LocalName.to_string loc }
3✔
398
    | { iv = `SourceLocationMod parent; _ } ->
37✔
399
        let page = Path.from_identifier (parent :> Path.any) in
400
        Ok { page; kind = `SourceAnchor; anchor = "" }
37✔
UNCOV
401
    | { iv = `SourcePage _ | `SourceDir _; _ } as p ->
×
402
        let page = Path.from_identifier (p :> Path.any) in
403
        Ok { page; kind = `Page; anchor = "" }
×
UNCOV
404
    | { iv = `AssetFile _; _ } as p ->
×
405
        let page = Path.from_identifier p in
UNCOV
406
        Ok { page; kind = `File; anchor = "" }
×
407

408
  let polymorphic_variant ~type_ident elt =
409
    let name_of_type_constr te =
152✔
410
      match te with
18✔
411
      | Odoc_model.Lang.TypeExpr.Constr (path, _) ->
18✔
412
          render_path (path :> Odoc_model.Paths.Path.t)
UNCOV
413
      | _ ->
×
414
          invalid_arg
415
            "DocOckHtml.Url.Polymorphic_variant_decl.name_of_type_constr"
416
    in
417
    match from_identifier type_ident with
UNCOV
418
    | Error e -> failwith (Error.to_string e)
×
419
    | Ok url -> (
152✔
420
        match elt with
421
        | Odoc_model.Lang.TypeExpr.Polymorphic_variant.Type te ->
18✔
422
            let kind = `Type in
423
            let suffix = name_of_type_constr te in
424
            add_suffix ~kind url suffix
18✔
425
        | Constructor { name; _ } ->
134✔
426
            let kind = `Constructor in
427
            let suffix = name in
428
            add_suffix ~kind url suffix)
429

430
  (** The anchor looks like
431
      [extension-decl-"Path.target_type"-FirstConstructor]. *)
432
  let extension_decl (decl : Odoc_model.Lang.Extension.t) =
433
    let page = Path.from_identifier (decl.parent :> Path.any) in
95✔
434
    let kind = `ExtensionDecl in
95✔
435
    let first_cons = Identifier.name (List.hd decl.constructors).id in
95✔
436
    let anchor = Format.asprintf "%a-%s" pp_kind kind first_cons in
95✔
437
    { page; kind; anchor }
95✔
438

UNCOV
439
  let source_anchor path anchor = { page = path; anchor; kind = `SourceAnchor }
×
440
end
441

442
type kind = Anchor.kind
443

444
type t = Anchor.t
445

446
let from_path page =
447
  { Anchor.page; anchor = ""; kind = (page.kind :> Anchor.kind) }
8,477✔
448

449
let from_identifier ~stop_before = function
450
  | { Odoc_model.Paths.Identifier.iv = #Path.any_pv; _ } as p
1,878✔
451
    when not stop_before ->
452
      Ok (from_path @@ Path.from_identifier p)
1,696✔
453
  | p -> Anchor.from_identifier p
4,701✔
454

455
let kind id =
456
  match Anchor.from_identifier id with
552✔
UNCOV
457
  | Error e -> failwith (Error.to_string e)
×
458
  | Ok { kind; _ } -> kind
552✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc