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

ocaml / odoc / 2168

10 Jul 2024 02:38PM UTC coverage: 71.437% (-0.4%) from 71.864%
2168

Pull #1142

github

web-flow
Merge 9bc2c3b35 into de54ed266
Pull Request #1142: Parsing of path-references to pages and modules

68 of 127 new or added lines in 6 files covered. (53.54%)

700 existing lines in 17 files now uncovered.

9794 of 13710 relevant lines covered (71.44%)

3534.91 hits per line

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

82.38
/src/document/generator.ml
1
(*
2
 * Copyright (c) 2016 Thomas Refis <trefis@janestreet.com>
3
 *
4
 * Permission to use, copy, modify, and distribute this software for any
5
 * purpose with or without fee is hereby granted, provided that the above
6
 * copyright notice and this permission notice appear in all copies.
7
 *
8
 * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
9
 * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
10
 * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
11
 * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
12
 * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
13
 * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
14
 * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
15
 *)
16

17
open Odoc_model.Names
18
module Location = Odoc_model.Location_
19
module Paths = Odoc_model.Paths
20
open Types
21
module O = Codefmt
22
open O.Infix
23

24
let tag tag t = O.span ~attr:tag t
1,140✔
25

26
let rec filter_map acc f = function
27
  | hd :: tl ->
125✔
UNCOV
28
      let acc = match f hd with Some x -> x :: acc | None -> acc in
×
29
      filter_map acc f tl
30
  | [] -> List.rev acc
26✔
31

32
let label t =
33
  match t with
42✔
34
  | Odoc_model.Lang.TypeExpr.Label s -> tag "label" (O.txt s)
18✔
35
  | Optional s -> tag "optlabel" (O.txt "?" ++ O.txt s)
24✔
36

37
let type_var tv = tag "type-var" (O.txt tv)
546✔
38

39
let enclose ~l ~r x = O.span (O.txt l ++ x ++ O.txt r)
234✔
40

41
let resolved p content =
42
  let link = { InternalLink.target = Resolved p; content; tooltip = None } in
5,299✔
43
  O.elt [ inline @@ InternalLink link ]
5,299✔
44

45
let path p content = resolved (Url.from_path p) content
2,277✔
46

47
let unresolved content =
48
  let link = { InternalLink.target = Unresolved; content; tooltip = None } in
34✔
49
  O.elt [ inline @@ InternalLink link ]
34✔
50

51
let path_to_id path =
52
  match Url.Anchor.from_identifier (path :> Paths.Identifier.t) with
5,695✔
UNCOV
53
  | Error _ -> None
×
54
  | Ok url -> Some url
5,695✔
55

56
let source_anchor source_loc =
57
  (* Remove when dropping support for OCaml < 4.08 *)
UNCOV
58
  let to_option = function Result.Ok x -> Some x | Result.Error _ -> None in
×
59
  match source_loc with
60
  | Some id ->
95✔
61
      Url.Anchor.from_identifier
62
        (id : Paths.Identifier.SourceLocation.t :> Paths.Identifier.t)
63
      |> to_option
95✔
64
  | _ -> None
5,877✔
65

66
let attach_expansion ?(status = `Default) (eq, o, e) page text =
1,209✔
67
  match page with
2,639✔
68
  | None -> O.documentedSrc text
529✔
69
  | Some (page : Page.t) ->
2,110✔
70
      let url = page.url in
71
      let summary = O.render text in
72
      let expansion =
2,110✔
73
        O.documentedSrc (O.txt eq ++ O.keyword o)
2,110✔
74
        @ DocumentedSrc.[ Subpage { status; content = page } ]
75
        @ O.documentedSrc (O.keyword e)
2,110✔
76
      in
77
      DocumentedSrc.
78
        [ Alternative (Expansion { summary; url; status; expansion }) ]
79

80
let mk_heading ?(level = 1) ?label text =
290✔
81
  let title = [ inline @@ Text text ] in
290✔
82
  Item.Heading { label; level; title; source_anchor = None }
83

84
(** Returns the preamble as an item. Stop the preamble at the first heading. The
85
    rest is inserted into [items]. *)
86
let prepare_preamble comment items =
87
  let preamble, first_comment =
2,555✔
88
    Utils.split_at
89
      ~f:(function
90
        | { Odoc_model.Location_.value = `Heading _; _ } -> true | _ -> false)
24✔
91
      comment
92
  in
93
  (Comment.standalone preamble, Comment.standalone first_comment @ items)
2,555✔
94

95
let make_expansion_page ~source_anchor url comments items =
96
  let comment = List.concat comments in
2,555✔
97
  let preamble, items = prepare_preamble comment items in
2,555✔
98
  { Page.preamble; items; url; source_anchor }
2,555✔
99

100
include Generator_signatures
101

102
module Make (Syntax : SYNTAX) = struct
103
  module Link : sig
104
    val from_path : Paths.Path.t -> text
105

106
    val from_fragment : Paths.Fragment.leaf -> text
107
  end = struct
108
    open Paths
109

110
    let rec from_path : Path.t -> text =
111
     fun path ->
112
      match path with
4,550✔
113
      | `Identifier (id, _) ->
4✔
114
          unresolved [ inline @@ Text (Identifier.name id) ]
4✔
UNCOV
115
      | `Substituted m -> from_path (m :> Path.t)
×
UNCOV
116
      | `SubstitutedMT m -> from_path (m :> Path.t)
×
UNCOV
117
      | `SubstitutedT m -> from_path (m :> Path.t)
×
118
      | `SubstitutedCT m -> from_path (m :> Path.t)
×
119
      | `Root root -> unresolved [ inline @@ Text root ]
6✔
120
      | `Forward root -> unresolved [ inline @@ Text root ] (* FIXME *)
×
121
      | `Dot (prefix, suffix) ->
6✔
122
          let link = from_path (prefix :> Path.t) in
123
          link ++ O.txt ("." ^ suffix)
6✔
UNCOV
124
      | `Apply (p1, p2) ->
×
125
          let link1 = from_path (p1 :> Path.t) in
UNCOV
126
          let link2 = from_path (p2 :> Path.t) in
×
UNCOV
127
          link1 ++ O.txt "(" ++ link2 ++ O.txt ")"
×
128
      | `Resolved _ when Paths.Path.is_hidden path ->
4,534✔
129
          let txt = Url.render_path path in
24✔
130
          unresolved [ inline @@ Text txt ]
24✔
131
      | `Resolved rp -> (
4,510✔
132
          (* If the path is pointing to an opaque module or module type
133
             there won't be a page generated - so we stop before; at
134
             the parent page, and link instead to the anchor representing
135
             the declaration of the opaque module(_type) *)
136
          let stop_before =
137
            match rp with
138
            | `OpaqueModule _ | `OpaqueModuleType _ -> true
6✔
139
            | _ -> false
4,354✔
140
          in
141
          let id = Paths.Path.Resolved.identifier rp in
142
          let txt = Url.render_path path in
4,510✔
143
          match Url.from_identifier ~stop_before id with
4,510✔
144
          | Ok href -> resolved href [ inline @@ Text txt ]
2,636✔
145
          | Error (Url.Error.Not_linkable _) -> O.txt txt
1,874✔
UNCOV
146
          | Error exn ->
×
UNCOV
147
              Printf.eprintf "Id.href failed: %S\n%!" (Url.Error.to_string exn);
×
148
              O.txt txt)
×
149

150
    let dot prefix suffix = prefix ^ "." ^ suffix
37✔
151

152
    let rec render_fragment_any : Fragment.t -> string =
153
     fun fragment ->
UNCOV
154
      match fragment with
×
UNCOV
155
      | `Resolved rr -> render_resolved_fragment rr
×
UNCOV
156
      | `Dot (`Root, suffix) -> suffix
×
UNCOV
157
      | `Dot (prefix, suffix) ->
×
UNCOV
158
          dot (render_fragment_any (prefix :> Fragment.t)) suffix
×
159
      | `Root -> assert false
160

161
    and render_resolved_fragment : Fragment.Resolved.t -> string =
162
      let open Fragment.Resolved in
163
      fun fragment ->
164
        match fragment with
280✔
165
        | `Root _ -> assert false
166
        | `Subst (_, rr) -> render_resolved_fragment (rr :> t)
6✔
167
        | `Alias (_, rr) -> render_resolved_fragment (rr :> t)
18✔
168
        | `Module (`Root _, s) -> ModuleName.to_string s
92✔
169
        | `Module_type (`Root _, s) -> ModuleTypeName.to_string s
24✔
170
        | `Type (`Root _, s) -> TypeName.to_string s
103✔
UNCOV
171
        | `Class (`Root _, s) -> ClassName.to_string s
×
UNCOV
172
        | `ClassType (`Root _, s) -> ClassTypeName.to_string s
×
173
        | `Module (rr, s) ->
6✔
174
            dot (render_resolved_fragment (rr :> t)) (ModuleName.to_string s)
6✔
175
        | `Module_type (rr, s) ->
12✔
176
            dot
177
              (render_resolved_fragment (rr :> t))
12✔
178
              (ModuleTypeName.to_string s)
12✔
179
        | `Type (rr, s) ->
19✔
180
            dot (render_resolved_fragment (rr :> t)) (TypeName.to_string s)
19✔
UNCOV
181
        | `Class (rr, s) ->
×
UNCOV
182
            dot (render_resolved_fragment (rr :> t)) (ClassName.to_string s)
×
UNCOV
183
        | `ClassType (rr, s) ->
×
UNCOV
184
            dot (render_resolved_fragment (rr :> t)) (ClassTypeName.to_string s)
×
UNCOV
185
        | `OpaqueModule r -> render_resolved_fragment (r :> t)
×
186

187
    let resolved_fragment_to_ir : Fragment.Resolved.leaf -> text =
188
     fun fragment ->
189
      let open Fragment in
219✔
190
      let id = Resolved.identifier (fragment :> Resolved.t) in
191
      let txt = render_resolved_fragment (fragment :> Resolved.t) in
219✔
192
      match Url.from_identifier ~stop_before:false id with
219✔
193
      | Ok href -> resolved href [ inline @@ Text txt ]
219✔
UNCOV
194
      | Error (Not_linkable _) -> unresolved [ inline @@ Text txt ]
×
UNCOV
195
      | Error exn ->
×
196
          Printf.eprintf "[FRAG] Id.href failed: %S\n%!"
UNCOV
197
            (Url.Error.to_string exn);
×
198
          unresolved [ inline @@ Text txt ]
×
199

200
    let from_fragment : Fragment.leaf -> text = function
201
      | `Resolved r
219✔
202
        when not (Fragment.Resolved.is_hidden (r :> Fragment.Resolved.t)) ->
219✔
203
          resolved_fragment_to_ir r
219✔
UNCOV
204
      | f ->
×
205
          let txt = render_fragment_any (f :> Fragment.t) in
UNCOV
206
          unresolved [ inline @@ Text txt ]
×
207
  end
208

209
  module Impl = struct
210
    let impl ~infos src =
211
      let l =
26✔
212
        infos
213
        |> List.sort (fun (_, (l1, e1)) (_, (l2, e2)) ->
214
               if l1 = l2 then compare e2 e1
125✔
215
                 (* If two intervals open at the same time, we open
216
                    first the one that closes last *)
217
               else compare l1 l2)
3,027✔
218
      in
219
      let get_src a b =
26✔
220
        let in_bound x = min (max x 0) (String.length src) in
1,590✔
221
        let a = in_bound a and b = in_bound b in
1,590✔
222
        let a, b = (min a b, max a b) in
1,590✔
223
        String.sub src a (b - a)
224
      in
225
      let plain_code = function
226
        | "" -> []
561✔
227
        | s -> [ Types.Source_page.Plain_code s ]
1,029✔
228
      in
229
      let min (a : int) b = if a < b then a else b in
151✔
230
      let rec extract from to_ list aux =
231
        match list with
1,590✔
232
        | (k, (loc_start, loc_end)) :: q when loc_start < to_ ->
1,538✔
233
            let loc_end = min loc_end to_ in
782✔
234
            (* In case of inconsistent [a  [b    a] b]
235
               we do                   [a  [b  b]a] *)
236
            let initial = plain_code (get_src from loc_start) in
782✔
237
            let next, q = extract loc_start loc_end q [] in
782✔
238
            extract loc_end to_ q
782✔
239
              ([ Types.Source_page.Tagged_code (k, List.rev next) ]
782✔
240
              @ initial @ aux)
241
        | q -> (plain_code (get_src from to_) @ aux, q)
808✔
242
      in
243
      let doc, _ = extract 0 (String.length src) l [] in
26✔
244
      List.rev doc
26✔
245
  end
246

247
  module Source_page : sig
248
    val source :
249
      Paths.Identifier.SourcePage.t ->
250
      Syntax_highlighter.infos ->
251
      Lang.Source_info.t ->
252
      string ->
253
      Source_page.t
254
  end = struct
255
    let path id = Url.Path.from_identifier id
26✔
256

257
    let to_link { Lang.Source_info.documentation; implementation } =
258
      let documentation =
33✔
259
        (* Since documentation link are not rendered, we comment the code to
260
           extract the href, and always output [None] *)
261
        ignore documentation;
262
        None
263
        (* let open Paths.Path.Resolved in *)
264
        (* match documentation with *)
265
        (* | Some (`Resolved p) when not (is_hidden (p :> t)) -> ( *)
266
        (*     let id = identifier (p :> t) in *)
267
        (*     match Url.from_identifier ~stop_before:false id with *)
268
        (*     | Ok link -> Some link *)
269
        (*     | _ -> None) *)
270
        (* | _ -> None *)
271
      in
272
      let implementation =
273
        match implementation with
274
        | Some (Odoc_model.Lang.Source_info.Resolved id) -> (
15✔
275
            match Url.Anchor.from_identifier (id :> Paths.Identifier.t) with
276
            | Ok url -> Some url
15✔
UNCOV
277
            | Error _ -> None)
×
278
        | _ -> None
18✔
279
      in
280
      Some (Source_page.Link { implementation; documentation })
281

282
    let info_of_info : Lang.Source_info.annotation -> Source_page.info option =
283
      function
284
      | Definition id -> (
92✔
285
          match id.iv with
286
          | `SourceLocation (_, def) -> Some (Anchor (DefName.to_string def))
88✔
287
          | `SourceLocationInternal (_, local) ->
4✔
288
              Some (Anchor (LocalName.to_string local))
4✔
UNCOV
289
          | _ -> None)
×
290
      | Module v -> to_link v
11✔
291
      | ModuleType v -> to_link v
1✔
292
      | Type v -> to_link v
6✔
293
      | Value v -> to_link v
15✔
294

295
    let source id syntax_info infos source_code =
296
      let url = path id in
26✔
297
      let mapper (info, loc) =
26✔
UNCOV
298
        match info_of_info info with Some x -> Some (x, loc) | None -> None
×
299
      in
300
      let infos = filter_map [] mapper infos in
301
      let syntax_info =
26✔
302
        List.map (fun (ty, loc) -> (Source_page.Syntax ty, loc)) syntax_info
657✔
303
      in
304
      let contents = Impl.impl ~infos:(infos @ syntax_info) source_code in
26✔
305
      { Source_page.url; contents }
26✔
306
  end
307

308
  module Type_expression : sig
309
    val type_expr : ?needs_parentheses:bool -> Lang.TypeExpr.t -> text
310

311
    val format_type_path :
312
      delim:[ `parens | `brackets ] -> Lang.TypeExpr.t list -> text -> text
313
  end = struct
314
    let rec te_variant (t : Odoc_model.Lang.TypeExpr.Polymorphic_variant.t) =
315
      let style_arguments ~constant arguments =
133✔
316
        (* Multiple arguments in a polymorphic variant constructor correspond
317
           to a conjunction of types, not a product: [`Lbl int&float].
318
           If constant is [true], the conjunction starts with an empty type,
319
           for instance [`Lbl &int].
320
        *)
321
        let wrapped_type_expr =
84✔
322
          (* type conjunction in Reason is printed as `Lbl (t1)&(t2)` *)
UNCOV
323
          if Syntax.Type.Variant.parenthesize_params then fun x ->
×
UNCOV
324
            enclose ~l:"(" ~r:")" (type_expr x)
×
325
          else fun x -> type_expr x
84✔
326
        in
327
        let arguments =
328
          O.list arguments ~sep:(O.txt " & ") ~f:wrapped_type_expr
84✔
329
        in
330
        if constant then O.txt "& " ++ arguments else arguments
12✔
331
      in
332
      let rec style_elements ~add_pipe = function
333
        | [] -> O.noop
133✔
334
        | first :: rest ->
181✔
335
            let first =
336
              match first with
337
              | Odoc_model.Lang.TypeExpr.Polymorphic_variant.Type te ->
6✔
338
                  let res = O.box_hv @@ type_expr te in
6✔
UNCOV
339
                  if add_pipe then O.sp ++ O.span (O.txt "| " ++ res) else res
×
340
              | Constructor { constant; name; arguments; _ } ->
175✔
341
                  let constr =
342
                    let name = "`" ^ name in
343
                    if add_pipe then O.span (O.txt ("| " ^ name))
54✔
344
                    else O.txt name
121✔
345
                  in
346
                  let res =
347
                    O.box_hv
348
                      (match arguments with
349
                      | [] -> constr
91✔
350
                      | _ ->
84✔
351
                          let arguments = style_arguments ~constant arguments in
352
                          O.span
84✔
353
                            (if Syntax.Type.Variant.parenthesize_params then
UNCOV
354
                               constr ++ arguments
×
355
                             else constr ++ O.txt " of" ++ O.sp ++ arguments))
84✔
356
                  in
357
                  if add_pipe then O.sp ++ res else res
54✔
358
            in
359
            first ++ style_elements ~add_pipe:true rest
181✔
360
      in
361
      let elements = style_elements ~add_pipe:false t.elements in
362
      O.box_hv_no_indent
133✔
363
      @@ O.span
133✔
364
           (match t.kind with
365
           | Fixed -> O.txt "[ " ++ elements ++ O.txt " ]"
37✔
366
           | Open -> O.txt "[> " ++ elements ++ O.txt " ]"
36✔
367
           | Closed [] -> O.txt "[< " ++ elements ++ O.txt " ]"
54✔
368
           | Closed lst ->
6✔
369
               let constrs = String.concat " " lst in
370
               O.txt "[< " ++ elements ++ O.txt (" " ^ constrs ^ " ]"))
6✔
371

372
    and te_object (t : Odoc_model.Lang.TypeExpr.Object.t) =
373
      let fields =
60✔
374
        O.list
375
          ~sep:(O.sp ++ O.txt Syntax.Obj.field_separator)
60✔
376
          t.fields
377
          ~f:(function
378
            | Odoc_model.Lang.TypeExpr.Object.Method { name; type_ } ->
90✔
379
                O.box_hv_no_indent
380
                @@ O.txt (name ^ Syntax.Type.annotation_separator)
90✔
381
                   ++ O.cut ++ type_expr type_
90✔
UNCOV
382
            | Inherit type_ -> O.box_hv_no_indent @@ type_expr type_)
×
383
      in
384
      let open_tag =
60✔
385
        if t.open_ then O.txt Syntax.Obj.open_tag_extendable
24✔
386
        else O.txt Syntax.Obj.open_tag_closed
36✔
387
      in
388
      let close_tag =
389
        if t.open_ then O.txt Syntax.Obj.close_tag_extendable
24✔
390
        else O.txt Syntax.Obj.close_tag_closed
36✔
391
      in
392
      O.span (open_tag ++ fields ++ close_tag)
60✔
393

394
    and format_type_path ~delim (params : Odoc_model.Lang.TypeExpr.t list)
395
        (path : text) : text =
396
      O.box_hv
3,165✔
397
      @@
398
      match params with
399
      | [] -> path
2,745✔
400
      | [ param ] ->
264✔
401
          let param = type_expr ~needs_parentheses:true param in
402
          let args =
264✔
403
            if Syntax.Type.parenthesize_constructor then
UNCOV
404
              O.txt "(" ++ param ++ O.txt ")"
×
405
            else param
264✔
406
          in
407
          Syntax.Type.handle_constructor_params path args
264✔
408
      | params ->
156✔
409
          let params = O.list params ~sep:(O.txt "," ++ O.sp) ~f:type_expr in
156✔
410
          let params =
156✔
411
            match delim with
412
            | `parens -> enclose ~l:"(" params ~r:")"
156✔
UNCOV
413
            | `brackets -> enclose ~l:"[" params ~r:"]"
×
414
          in
415
          Syntax.Type.handle_constructor_params path (O.box_hv params)
156✔
416

417
    and type_expr ?(needs_parentheses = false) (t : Odoc_model.Lang.TypeExpr.t)
3,113✔
418
        =
419
      match t with
4,430✔
420
      | Var s -> type_var (Syntax.Type.var_prefix ^ s)
546✔
UNCOV
421
      | Any -> type_var Syntax.Type.any
×
422
      | Alias (te, alias) ->
60✔
423
          type_expr ~needs_parentheses:true te
60✔
424
          ++ O.txt " " ++ O.keyword "as" ++ O.txt " '" ++ O.txt alias
60✔
425
      | Arrow (None, src, dst) ->
302✔
426
          let res =
427
            O.span
302✔
428
              ((O.box_hv @@ type_expr ~needs_parentheses:true src)
302✔
429
              ++ O.txt " " ++ Syntax.Type.arrow)
302✔
430
            ++ O.sp ++ type_expr dst
302✔
431
            (* ++ O.end_hv *)
432
          in
433
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
24✔
434
      | Arrow (Some lbl, src, dst) ->
42✔
435
          let res =
436
            O.span
42✔
437
              ((O.box_hv
42✔
438
               @@ label lbl ++ O.txt ":" ++ O.cut
42✔
439
                  ++ (O.box_hv @@ type_expr ~needs_parentheses:true src))
42✔
440
              ++ O.txt " " ++ Syntax.Type.arrow)
42✔
441
            ++ O.sp ++ type_expr dst
42✔
442
          in
443
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
12✔
444
      | Tuple lst ->
130✔
445
          let res =
446
            O.box_hv_no_indent
447
              (O.list lst ~sep:Syntax.Type.Tuple.element_separator
130✔
448
                 ~f:(type_expr ~needs_parentheses:true))
449
          in
UNCOV
450
          if Syntax.Type.Tuple.always_parenthesize || needs_parentheses then
×
451
            enclose ~l:"(" res ~r:")"
24✔
452
          else res
106✔
453
      | Constr (path, args) ->
3,115✔
454
          let link = Link.from_path (path :> Paths.Path.t) in
455
          format_type_path ~delim:`parens args link
3,115✔
456
      | Polymorphic_variant v -> te_variant v
133✔
457
      | Object o -> te_object o
60✔
458
      | Class (path, args) ->
6✔
459
          format_type_path ~delim:`brackets args
460
            (Link.from_path (path :> Paths.Path.t))
6✔
461
      | Poly (polyvars, t) ->
18✔
462
          O.txt ("'" ^ String.concat " '" polyvars ^ ". ") ++ type_expr t
18✔
463
      | Package pkg ->
18✔
464
          enclose ~l:"(" ~r:")"
465
            (O.keyword "module" ++ O.txt " "
18✔
466
            ++ Link.from_path (pkg.path :> Paths.Path.t)
18✔
467
            ++
18✔
468
            match pkg.substitutions with
469
            | [] -> O.noop
12✔
470
            | fst :: lst ->
6✔
471
                O.sp
472
                ++ O.box_hv (O.keyword "with" ++ O.txt " " ++ package_subst fst)
6✔
473
                ++ O.list lst ~f:(fun s ->
6✔
474
                       O.cut
6✔
475
                       ++ (O.box_hv
6✔
476
                          @@ O.txt " " ++ O.keyword "and" ++ O.txt " "
6✔
477
                             ++ package_subst s)))
6✔
478

479
    and package_subst
480
        ((frag_typ, te) : Paths.Fragment.Type.t * Odoc_model.Lang.TypeExpr.t) :
481
        text =
482
      let typath = Link.from_fragment (frag_typ :> Paths.Fragment.leaf) in
12✔
483
      O.keyword "type" ++ O.txt " " ++ typath ++ O.txt " =" ++ O.sp
12✔
484
      ++ type_expr te
12✔
485
  end
486

487
  open Type_expression
488

489
  (* Also handles constructor declarations for exceptions and extensible
490
     variants, and exposes a few helpers used in formatting classes and signature
491
     constraints. *)
492
  module Type_declaration : sig
493
    val type_decl :
494
      ?is_substitution:bool ->
495
      Lang.Signature.recursive * Lang.TypeDecl.t ->
496
      Item.t
497

498
    val extension : Lang.Extension.t -> Item.t
499

500
    val record : Lang.TypeDecl.Field.t list -> DocumentedSrc.one list
501

502
    val exn : Lang.Exception.t -> Item.t
503

504
    val format_params :
505
      ?delim:[ `parens | `brackets ] -> Lang.TypeDecl.param list -> text
506

507
    val format_manifest :
508
      ?is_substitution:bool ->
509
      ?compact_variants:bool ->
510
      Lang.TypeDecl.Equation.t ->
511
      text * bool
512

513
    val format_constraints : (Lang.TypeExpr.t * Lang.TypeExpr.t) list -> text
514
  end = struct
515
    let record fields =
516
      let field mutable_ id typ =
72✔
517
        match Url.from_identifier ~stop_before:true id with
120✔
UNCOV
518
        | Error e -> failwith (Url.Error.to_string e)
×
519
        | Ok url ->
120✔
520
            let name = Paths.Identifier.name id in
521
            let attrs =
120✔
522
              [ "def"; "record"; Url.Anchor.string_of_kind url.kind ]
120✔
523
            in
524
            let cell =
525
              (* O.td ~a:[ O.a_class ["def"; kind ] ]
526
               *   [O.a ~a:[O.a_href ("#" ^ anchor); O.a_class ["anchor"]] []
527
               *   ; *)
528
              O.code
529
                ((if mutable_ then O.keyword "mutable" ++ O.txt " " else O.noop)
18✔
530
                ++ O.txt name
120✔
531
                ++ O.txt Syntax.Type.annotation_separator
120✔
532
                ++ type_expr typ
120✔
533
                ++ O.txt Syntax.Type.Record.field_separator)
120✔
534
              (* ] *)
535
            in
536
            (url, attrs, cell)
120✔
537
      in
538
      let rows =
539
        fields
540
        |> List.map (fun fld ->
541
               let open Odoc_model.Lang.TypeDecl.Field in
120✔
542
               let url, attrs, code =
543
                 field fld.mutable_ (fld.id :> Paths.Identifier.t) fld.type_
544
               in
545
               let anchor = Some url in
120✔
546
               let rhs = Comment.to_ir fld.doc in
547
               let doc = if not (Comment.has_doc fld.doc) then [] else rhs in
48✔
548
               let markers = Syntax.Comment.markers in
549
               DocumentedSrc.Documented { anchor; attrs; code; doc; markers })
550
      in
551
      let content =
72✔
552
        O.documentedSrc (O.txt "{") @ rows @ O.documentedSrc (O.txt "}")
72✔
553
      in
554
      content
555

556
    let constructor :
557
        Paths.Identifier.t ->
558
        Odoc_model.Lang.TypeDecl.Constructor.argument ->
559
        Odoc_model.Lang.TypeExpr.t option ->
560
        DocumentedSrc.t =
561
     fun id args ret_type ->
562
      let name = Paths.Identifier.name id in
552✔
563
      let kind = Url.(kind id |> Anchor.string_of_kind) in
552✔
564
      let cstr = tag kind (O.txt name) in
552✔
565
      let is_gadt, ret_type =
552✔
566
        match ret_type with
567
        | None -> (false, O.noop)
420✔
568
        | Some te ->
132✔
569
            let constant = match args with Tuple [] -> true | _ -> false in
42✔
570
            let ret_type =
571
              O.txt " "
132✔
572
              ++ (if constant then O.txt ":" else Syntax.Type.GADT.arrow)
42✔
573
              ++ O.txt " " ++ type_expr te
132✔
574
            in
575
            (true, ret_type)
132✔
576
      in
577
      match args with
578
      | Tuple [] -> O.documentedSrc (cstr ++ ret_type)
243✔
579
      | Tuple lst ->
285✔
580
          let params =
581
            O.list lst ~sep:Syntax.Type.Tuple.element_separator
582
              ~f:(type_expr ~needs_parentheses:is_gadt)
583
          in
584
          O.documentedSrc
285✔
585
            (cstr
586
            ++ (if Syntax.Type.Variant.parenthesize_params then
285✔
UNCOV
587
                  O.txt "(" ++ params ++ O.txt ")"
×
588
                else
589
                  (if is_gadt then O.txt Syntax.Type.annotation_separator
84✔
590
                   else O.txt " " ++ O.keyword "of" ++ O.txt " ")
201✔
591
                  ++ params)
285✔
592
            ++ ret_type)
285✔
593
      | Record fields ->
24✔
594
          if is_gadt then
595
            O.documentedSrc (cstr ++ O.txt Syntax.Type.annotation_separator)
6✔
596
            @ record fields @ O.documentedSrc ret_type
6✔
597
          else
598
            O.documentedSrc (cstr ++ O.txt " " ++ O.keyword "of" ++ O.txt " ")
18✔
599
            @ record fields
18✔
600

601
    let variant cstrs : DocumentedSrc.t =
602
      let constructor id args res =
206✔
603
        match Url.from_identifier ~stop_before:true id with
385✔
UNCOV
604
        | Error e -> failwith (Url.Error.to_string e)
×
605
        | Ok url ->
385✔
606
            let attrs =
607
              [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ]
385✔
608
            in
609
            let content =
610
              let doc = constructor id args res in
611
              O.documentedSrc (O.txt "| ") @ doc
385✔
612
            in
613
            (url, attrs, content)
614
      in
615
      match cstrs with
616
      | [] -> O.documentedSrc (O.txt "|")
6✔
617
      | _ :: _ ->
200✔
618
          let rows =
619
            cstrs
620
            |> List.map (fun cstr ->
621
                   let open Odoc_model.Lang.TypeDecl.Constructor in
385✔
622
                   let url, attrs, code =
623
                     constructor
624
                       (cstr.id :> Paths.Identifier.t)
625
                       cstr.args cstr.res
626
                   in
627
                   let anchor = Some url in
385✔
628
                   let rhs = Comment.to_ir cstr.doc in
629
                   let doc =
385✔
630
                     if not (Comment.has_doc cstr.doc) then [] else rhs
73✔
631
                   in
632
                   let markers = Syntax.Comment.markers in
633
                   DocumentedSrc.Nested { anchor; attrs; code; doc; markers })
634
          in
635
          rows
200✔
636

637
    let extension_constructor (t : Odoc_model.Lang.Extension.Constructor.t) =
638
      let id = (t.id :> Paths.Identifier.t) in
117✔
639
      match Url.from_identifier ~stop_before:true id with
UNCOV
640
      | Error e -> failwith (Url.Error.to_string e)
×
641
      | Ok url ->
117✔
642
          let anchor = Some url in
643
          let attrs =
644
            [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ]
117✔
645
          in
646
          let code =
647
            O.documentedSrc (O.txt "| ") @ constructor id t.args t.res
117✔
648
          in
649
          let doc = Comment.to_ir t.doc in
650
          let markers = Syntax.Comment.markers in
117✔
651
          DocumentedSrc.Nested { anchor; attrs; code; doc; markers }
652

653
    let extension (t : Odoc_model.Lang.Extension.t) =
654
      let prefix =
95✔
655
        O.keyword "type" ++ O.txt " "
95✔
656
        ++ Link.from_path (t.type_path :> Paths.Path.t)
95✔
657
        ++ O.txt " +=" ++ O.sp
95✔
658
        ++
659
        if t.private_ then O.keyword Syntax.Type.private_keyword ++ O.sp
6✔
660
        else O.noop
89✔
661
      in
662
      let content =
95✔
663
        O.documentedSrc prefix
95✔
664
        @ List.map extension_constructor t.constructors
95✔
665
        @ O.documentedSrc
95✔
UNCOV
666
            (if Syntax.Type.type_def_semicolon then O.txt ";" else O.noop)
×
667
      in
668
      let attr = [ "type"; "extension" ] in
669
      let anchor = Some (Url.Anchor.extension_decl t) in
95✔
670
      let doc = Comment.to_ir t.doc in
671
      let source_anchor =
95✔
672
        (* Take the anchor from the first constructor only for consistency with
673
           regular variants. *)
674
        match t.constructors with
675
        | hd :: _ -> source_anchor hd.source_loc
95✔
UNCOV
676
        | [] -> None
×
677
      in
678
      Item.Declaration { attr; anchor; doc; content; source_anchor }
679

680
    let exn (t : Odoc_model.Lang.Exception.t) =
681
      let cstr = constructor (t.id :> Paths.Identifier.t) t.args t.res in
50✔
682
      let content =
50✔
683
        O.documentedSrc (O.keyword "exception" ++ O.txt " ")
50✔
684
        @ cstr
685
        @ O.documentedSrc
50✔
UNCOV
686
            (if Syntax.Type.Exception.semicolon then O.txt ";" else O.noop)
×
687
      in
688
      let attr = [ "exception" ] in
689
      let anchor = path_to_id t.id in
690
      let doc = Comment.to_ir t.doc in
50✔
691
      let source_anchor = source_anchor t.source_loc in
50✔
692
      Item.Declaration { attr; anchor; doc; content; source_anchor }
50✔
693

694
    let polymorphic_variant ~type_ident
695
        (t : Odoc_model.Lang.TypeExpr.Polymorphic_variant.t) =
696
      let row item =
68✔
697
        let kind_approx, cstr, doc =
154✔
698
          match item with
699
          | Odoc_model.Lang.TypeExpr.Polymorphic_variant.Type te ->
18✔
700
              ("unknown", O.documentedSrc (type_expr te), None)
18✔
701
          | Constructor { constant; name; arguments; doc; _ } -> (
136✔
702
              let cstr = "`" ^ name in
703
              ( "constructor",
704
                (match arguments with
705
                | [] -> O.documentedSrc (O.txt cstr)
74✔
706
                | _ ->
62✔
707
                    (* Multiple arguments in a polymorphic variant constructor correspond
708
                       to a conjunction of types, not a product: [`Lbl int&float].
709
                       If constant is [true], the conjunction starts with an empty type,
710
                       for instance [`Lbl &int].
711
                    *)
712
                    let wrapped_type_expr =
713
                      (* type conjunction in Reason is printed as `Lbl (t1)&(t2)` *)
UNCOV
714
                      if Syntax.Type.Variant.parenthesize_params then fun x ->
×
UNCOV
715
                        O.txt "(" ++ type_expr x ++ O.txt ")"
×
716
                      else fun x -> type_expr x
62✔
717
                    in
718
                    let params =
719
                      O.box_hv
720
                      @@ O.list arguments
62✔
721
                           ~sep:(O.txt " &" ++ O.sp)
62✔
722
                           ~f:wrapped_type_expr
723
                    in
724
                    let params =
62✔
UNCOV
725
                      if constant then O.txt "& " ++ params else params
×
726
                    in
727
                    O.documentedSrc
62✔
728
                      (O.txt cstr
62✔
729
                      ++
62✔
UNCOV
730
                      if Syntax.Type.Variant.parenthesize_params then params
×
731
                      else O.txt " " ++ O.keyword "of" ++ O.sp ++ params)),
62✔
732
                match doc with [] -> None | _ -> Some (Comment.to_ir doc) ))
12✔
733
        in
734
        let markers = Syntax.Comment.markers in
735
        try
736
          let url = Url.Anchor.polymorphic_variant ~type_ident item in
737
          let attrs =
154✔
738
            [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ]
154✔
739
          in
740
          let anchor = Some url in
741
          let code = O.documentedSrc (O.txt "| ") @ cstr in
154✔
742
          let doc = match doc with None -> [] | Some doc -> doc in
12✔
743
          DocumentedSrc.Nested { attrs; anchor; code; doc; markers }
UNCOV
744
        with Failure s ->
×
745
          Printf.eprintf "ERROR: %s\n%!" s;
UNCOV
746
          let code = O.documentedSrc (O.txt "| ") @ cstr in
×
747
          let attrs = [ "def"; kind_approx ] in
748
          let doc = [] in
749
          let anchor = None in
750
          DocumentedSrc.Nested { attrs; anchor; code; doc; markers }
751
      in
752
      let variants = List.map row t.elements in
753
      let intro, ending =
68✔
754
        match t.kind with
755
        | Fixed -> (O.documentedSrc (O.txt "[ "), O.documentedSrc (O.txt " ]"))
62✔
756
        | Open -> (O.documentedSrc (O.txt "[> "), O.documentedSrc (O.txt " ]"))
6✔
UNCOV
757
        | Closed [] ->
×
UNCOV
758
            (O.documentedSrc (O.txt "[< "), O.documentedSrc (O.txt " ]"))
×
UNCOV
759
        | Closed lst ->
×
760
            let constrs = String.concat " " lst in
UNCOV
761
            ( O.documentedSrc (O.txt "[< "),
×
UNCOV
762
              O.documentedSrc (O.txt (" " ^ constrs ^ " ]")) )
×
763
      in
764
      intro @ variants @ ending
765

766
    let format_params :
767
          'row.
768
          ?delim:[ `parens | `brackets ] ->
769
          Odoc_model.Lang.TypeDecl.param list ->
770
          text =
771
     fun ?(delim = `parens) params ->
348✔
772
      let format_param { Odoc_model.Lang.TypeDecl.desc; variance; injectivity }
416✔
773
          =
774
        let desc =
456✔
775
          match desc with
776
          | Odoc_model.Lang.TypeDecl.Any -> [ "_" ]
30✔
777
          | Var s -> [ "'"; s ]
426✔
778
        in
779
        let var_desc =
780
          match variance with
781
          | None -> desc
444✔
782
          | Some Odoc_model.Lang.TypeDecl.Pos -> "+" :: desc
6✔
783
          | Some Odoc_model.Lang.TypeDecl.Neg -> "-" :: desc
6✔
784
        in
UNCOV
785
        let final = if injectivity then "!" :: var_desc else var_desc in
×
786
        String.concat "" final
787
      in
788
      O.txt
789
        (match params with
790
        | [] -> ""
44✔
791
        | [ x ] -> format_param x |> Syntax.Type.handle_format_params
288✔
792
        | lst -> (
84✔
793
            let params = String.concat ", " (List.map format_param lst) in
84✔
UNCOV
794
            (match delim with `parens -> "(" | `brackets -> "[")
×
795
            ^ params
UNCOV
796
            ^ match delim with `parens -> ")" | `brackets -> "]"))
×
797

798
    let format_constraints constraints =
799
      O.list constraints ~f:(fun (t1, t2) ->
2,390✔
800
          O.sp
78✔
801
          ++ (O.box_hv
78✔
802
             @@ O.keyword "constraint" ++ O.sp
78✔
803
                ++ O.box_hv_no_indent (type_expr t1)
78✔
804
                ++ O.txt " =" ++ O.sp
78✔
805
                ++ O.box_hv_no_indent (type_expr t2)))
78✔
806

807
    let format_manifest :
808
          'inner_row 'outer_row.
809
          ?is_substitution:bool ->
810
          ?compact_variants:bool ->
811
          Odoc_model.Lang.TypeDecl.Equation.t ->
812
          text * bool =
813
     fun ?(is_substitution = false) ?(compact_variants = true) equation ->
78✔
814
      let _ = compact_variants in
2,316✔
815
      (* TODO *)
816
      let private_ = equation.private_ in
817
      match equation.manifest with
818
      | None -> (O.noop, private_)
1,355✔
819
      | Some t ->
961✔
820
          let manifest =
821
            O.txt (if is_substitution then " :=" else " =")
18✔
822
            ++ O.sp
961✔
823
            ++ (if private_ then
961✔
824
                  O.keyword Syntax.Type.private_keyword ++ O.txt " "
6✔
825
                else O.noop)
955✔
826
            ++ type_expr t
961✔
827
          in
828
          (manifest, false)
961✔
829

830
    let type_decl ?(is_substitution = false)
2,288✔
831
        ((recursive, t) : Lang.Signature.recursive * Lang.TypeDecl.t) =
832
      let keyword' =
2,306✔
833
        match recursive with
UNCOV
834
        | Ordinary | Rec -> O.keyword "type"
×
835
        | And -> O.keyword "and"
14✔
836
        | Nonrec -> O.keyword "type" ++ O.txt " " ++ O.keyword "nonrec"
7✔
837
      in
838
      let tyname = Paths.Identifier.name t.id in
839
      let tconstr =
2,306✔
840
        match t.equation.params with
841
        | [] -> O.txt tyname
1,976✔
842
        | l ->
330✔
843
            let params = format_params l in
844
            Syntax.Type.handle_constructor_params (O.txt tyname) params
330✔
845
      in
846
      let intro = keyword' ++ O.txt " " ++ tconstr in
2,306✔
847
      let constraints = format_constraints t.equation.constraints in
2,306✔
848
      let manifest, need_private, long_prefix =
2,306✔
849
        match t.equation.manifest with
850
        | Some (Odoc_model.Lang.TypeExpr.Polymorphic_variant variant) ->
68✔
851
            let code =
852
              polymorphic_variant
853
                ~type_ident:(t.id :> Paths.Identifier.t)
854
                variant
855
            in
856
            let manifest =
68✔
857
              O.documentedSrc
68✔
858
                (O.ignore intro
68✔
UNCOV
859
                ++ O.txt (if is_substitution then " :=" else " =")
×
860
                ++ O.sp
68✔
861
                ++
68✔
862
                if t.equation.private_ then
863
                  O.keyword Syntax.Type.private_keyword ++ O.txt " "
6✔
864
                else O.noop)
62✔
865
              @ code
866
            in
867
            (manifest, false, O.noop)
868
        | _ ->
2,238✔
869
            let manifest, need_private =
870
              format_manifest ~is_substitution t.equation
871
            in
872
            let text = O.ignore intro ++ manifest in
2,238✔
873
            (O.documentedSrc @@ text, need_private, text)
2,238✔
874
      in
875
      let representation =
876
        match t.representation with
877
        | None -> []
2,006✔
878
        | Some repr ->
300✔
879
            let content =
880
              match repr with
881
              | Extensible -> O.documentedSrc (O.txt "..")
46✔
882
              | Variant cstrs -> variant cstrs
206✔
883
              | Record fields -> record fields
48✔
884
            in
885
            if List.length content > 0 then
300✔
886
              O.documentedSrc
300✔
887
                (O.ignore long_prefix ++ O.txt " =" ++ O.sp
300✔
888
                ++
300✔
889
                if need_private then
890
                  O.keyword Syntax.Type.private_keyword ++ O.txt " "
6✔
891
                else O.noop)
294✔
892
              @ content
893
            else []
×
894
      in
895
      let content =
896
        O.documentedSrc intro @ manifest @ representation
2,306✔
897
        @ O.documentedSrc constraints
2,306✔
898
        @ O.documentedSrc
2,306✔
UNCOV
899
            (if Syntax.Type.type_def_semicolon then O.txt ";" else O.noop)
×
900
      in
901
      let attr = "type" :: (if is_substitution then [ "subst" ] else []) in
18✔
902
      let anchor = path_to_id t.id in
903
      let doc = Comment.to_ir t.doc in
2,306✔
904
      let source_anchor = source_anchor t.source_loc in
2,306✔
905
      Item.Declaration { attr; anchor; doc; content; source_anchor }
2,306✔
906
  end
907

908
  open Type_declaration
909

910
  module Value : sig
911
    val value : Lang.Value.t -> Item.t
912
  end = struct
913
    let value (t : Odoc_model.Lang.Value.t) =
914
      let extra_attr, semicolon =
610✔
915
        match t.value with
916
        | Abstract -> ([], Syntax.Value.semicolon)
592✔
917
        | External _ -> ([ "external" ], Syntax.Type.External.semicolon)
18✔
918
      in
919
      let name = Paths.Identifier.name t.id in
920
      let content =
610✔
921
        O.documentedSrc
922
          (O.box_hv
610✔
923
          @@ O.keyword Syntax.Value.variable_keyword
610✔
924
             ++ O.txt " " ++ O.txt name
610✔
925
             ++ O.txt Syntax.Type.annotation_separator
610✔
926
             ++ O.cut ++ type_expr t.type_
610✔
UNCOV
927
             ++ if semicolon then O.txt ";" else O.noop)
×
928
      in
929
      let attr = [ "value" ] @ extra_attr in
610✔
930
      let anchor = path_to_id t.id in
931
      let doc = Comment.to_ir t.doc in
610✔
932
      let source_anchor = source_anchor t.source_loc in
610✔
933
      Item.Declaration { attr; anchor; doc; content; source_anchor }
610✔
934
  end
935

936
  open Value
937

938
  (* This chunk of code is responsible for sectioning list of items
939
     according to headings by extracting headings as Items.
940

941
     TODO: This sectioning would be better done as a pass on the model directly.
942
  *)
943
  module Sectioning : sig
944
    open Odoc_model
945

946
    val comment_items : Comment.docs -> Item.t list
947

948
    val docs : Comment.docs -> Item.t list * Item.t list
949
  end = struct
950
    let take_until_heading_or_end (docs : Odoc_model.Comment.docs) =
951
      let content, _, rest =
501✔
952
        Doctree.Take.until docs ~classify:(fun b ->
953
            match b.Location.value with
1,047✔
954
            | `Heading _ -> Stop_and_keep
128✔
955
            | #Odoc_model.Comment.attached_block_element as doc ->
919✔
956
                let content = Comment.attached_block_element doc in
957
                Accum content)
919✔
958
      in
959
      (content, rest)
501✔
960

961
    let comment_items (input0 : Odoc_model.Comment.docs) =
962
      let rec loop input_comment acc =
727✔
963
        match input_comment with
1,818✔
964
        | [] -> List.rev acc
727✔
965
        | element :: input_comment -> (
1,091✔
966
            match element.Location.value with
967
            | `Heading h ->
590✔
968
                let item = Comment.heading h in
969
                loop input_comment (item :: acc)
590✔
970
            | _ ->
501✔
971
                let content, input_comment =
972
                  take_until_heading_or_end (element :: input_comment)
973
                in
974
                let item = Item.Text content in
501✔
975
                loop input_comment (item :: acc))
976
      in
977
      loop input0 []
978

979
    (* For doc pages, we want the header to contain everything until
980
       the first heading, then everything before the next heading which
981
       is either lower, or a section.
982
    *)
983
    let docs input_comment =
984
      let items = comment_items input_comment in
42✔
985
      let until_first_heading, o, items =
42✔
986
        Doctree.Take.until items ~classify:(function
987
          | Item.Heading h as i -> Stop_and_accum ([ i ], Some h.level)
42✔
UNCOV
988
          | i -> Accum [ i ])
×
989
      in
990
      match o with
42✔
UNCOV
991
      | None -> (until_first_heading, items)
×
992
      | Some level ->
42✔
UNCOV
993
          let max_level = if level = 1 then 2 else level in
×
994
          let before_second_heading, _, items =
995
            Doctree.Take.until items ~classify:(function
996
              | Item.Heading h when h.level >= max_level -> Stop_and_keep
7✔
997
              | i -> Accum [ i ])
27✔
998
          in
999
          let header = until_first_heading @ before_second_heading in
42✔
1000
          (header, items)
1001
  end
1002

1003
  module Class : sig
1004
    val class_ : Lang.Class.t -> Item.t
1005

1006
    val class_type : Lang.ClassType.t -> Item.t
1007
  end = struct
1008
    let class_type_expr (cte : Odoc_model.Lang.ClassType.expr) =
1009
      match cte with
187✔
1010
      | Constr (path, args) ->
44✔
1011
          let link = Link.from_path (path :> Paths.Path.t) in
1012
          format_type_path ~delim:`brackets args link
44✔
1013
      | Signature _ ->
143✔
1014
          Syntax.Class.open_tag ++ O.txt " ... " ++ Syntax.Class.close_tag
143✔
1015

1016
    let method_ (t : Odoc_model.Lang.Method.t) =
1017
      let name = Paths.Identifier.name t.id in
66✔
1018
      let virtual_ =
66✔
1019
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
6✔
1020
      in
1021
      let private_ =
1022
        if t.private_ then O.keyword "private" ++ O.txt " " else O.noop
6✔
1023
      in
1024
      let content =
1025
        O.documentedSrc
1026
          (O.keyword "method" ++ O.txt " " ++ private_ ++ virtual_ ++ O.txt name
66✔
1027
          ++ O.txt Syntax.Type.annotation_separator
66✔
1028
          ++ type_expr t.type_)
66✔
1029
      in
1030
      let attr = [ "method" ] in
66✔
1031
      let anchor = path_to_id t.id in
1032
      let doc = Comment.to_ir t.doc in
66✔
1033
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
66✔
1034

1035
    let instance_variable (t : Odoc_model.Lang.InstanceVariable.t) =
1036
      let name = Paths.Identifier.name t.id in
12✔
1037
      let virtual_ =
12✔
1038
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
6✔
1039
      in
1040
      let mutable_ =
1041
        if t.mutable_ then O.keyword "mutable" ++ O.txt " " else O.noop
6✔
1042
      in
1043
      let content =
1044
        O.documentedSrc
1045
          (O.keyword "val" ++ O.txt " " ++ mutable_ ++ virtual_ ++ O.txt name
12✔
1046
          ++ O.txt Syntax.Type.annotation_separator
12✔
1047
          ++ type_expr t.type_)
12✔
1048
      in
1049
      let attr = [ "value"; "instance-variable" ] in
12✔
1050
      let anchor = path_to_id t.id in
1051
      let doc = Comment.to_ir t.doc in
12✔
1052
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
12✔
1053

1054
    let inherit_ (ih : Lang.ClassSignature.Inherit.t) =
1055
      let cte =
12✔
1056
        match ih.expr with
1057
        | Signature _ -> assert false (* Bold. *)
1058
        | cty -> cty
12✔
1059
      in
1060
      let content =
1061
        O.documentedSrc (O.keyword "inherit" ++ O.txt " " ++ class_type_expr cte)
12✔
1062
      in
1063
      let attr = [ "inherit" ] in
12✔
1064
      let anchor = None in
1065
      let doc = Comment.to_ir ih.doc in
1066
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
12✔
1067

1068
    let constraint_ (cst : Lang.ClassSignature.Constraint.t) =
1069
      let content =
6✔
1070
        O.documentedSrc (format_constraints [ (cst.left, cst.right) ])
6✔
1071
      in
1072
      let attr = [] in
6✔
1073
      let anchor = None in
1074
      let doc = Comment.to_ir cst.doc in
1075
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
6✔
1076

1077
    let class_signature (c : Lang.ClassSignature.t) =
1078
      let rec loop l acc_items =
175✔
1079
        match l with
289✔
1080
        | [] -> List.rev acc_items
175✔
1081
        | item :: rest -> (
114✔
1082
            let continue item = loop rest (item :: acc_items) in
96✔
1083
            match (item : Lang.ClassSignature.item) with
1084
            | Inherit cty -> continue @@ inherit_ cty
12✔
1085
            | Method m -> continue @@ method_ m
66✔
1086
            | InstanceVariable v -> continue @@ instance_variable v
12✔
1087
            | Constraint cst -> continue @@ constraint_ cst
6✔
1088
            | Comment `Stop ->
6✔
1089
                let rest =
1090
                  Utils.skip_until rest ~p:(function
1091
                    | Lang.ClassSignature.Comment `Stop -> true
6✔
1092
                    | _ -> false)
6✔
1093
                in
1094
                loop rest acc_items
6✔
1095
            | Comment (`Docs c) ->
12✔
1096
                let items = Sectioning.comment_items c in
1097
                loop rest (List.rev_append items acc_items))
12✔
1098
      in
1099
      (* FIXME: use [t.self] *)
1100
      (c.doc, loop c.items [])
175✔
1101

1102
    let rec class_decl (cd : Odoc_model.Lang.Class.decl) =
1103
      match cd with
137✔
1104
      | ClassType expr -> class_type_expr expr
125✔
1105
      (* TODO: factorize the following with [type_expr] *)
1106
      | Arrow (None, src, dst) ->
12✔
1107
          O.span
12✔
1108
            (type_expr ~needs_parentheses:true src
12✔
1109
            ++ O.txt " " ++ Syntax.Type.arrow)
12✔
1110
          ++ O.txt " " ++ class_decl dst
12✔
UNCOV
1111
      | Arrow (Some lbl, src, dst) ->
×
UNCOV
1112
          O.span
×
UNCOV
1113
            (label lbl ++ O.txt ":"
×
UNCOV
1114
            ++ type_expr ~needs_parentheses:true src
×
UNCOV
1115
            ++ O.txt " " ++ Syntax.Type.arrow)
×
UNCOV
1116
          ++ O.txt " " ++ class_decl dst
×
1117

1118
    let class_ (t : Odoc_model.Lang.Class.t) =
1119
      let name = Paths.Identifier.name t.id in
125✔
1120
      let params =
125✔
1121
        match t.params with
1122
        | [] -> O.noop
107✔
1123
        | _ :: _ as params -> format_params ~delim:`brackets params ++ O.txt " "
18✔
1124
      in
1125
      let virtual_ =
1126
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
18✔
1127
      in
1128

1129
      let source_anchor = source_anchor t.source_loc in
1130
      let cname, expansion, expansion_doc =
125✔
1131
        match t.expansion with
UNCOV
1132
        | None -> (O.documentedSrc @@ O.txt name, None, None)
×
1133
        | Some csig ->
125✔
1134
            let expansion_doc, items = class_signature csig in
1135
            let url = Url.Path.from_identifier t.id in
125✔
1136
            let page =
125✔
1137
              make_expansion_page ~source_anchor url [ t.doc; expansion_doc ]
1138
                items
1139
            in
1140
            ( O.documentedSrc @@ path url [ inline @@ Text name ],
125✔
1141
              Some page,
1142
              Some expansion_doc )
1143
      in
1144
      let summary =
1145
        O.txt Syntax.Type.annotation_separator ++ class_decl t.type_
125✔
1146
      in
1147
      let cd =
125✔
1148
        attach_expansion
1149
          (Syntax.Type.annotation_separator, "object", "end")
1150
          expansion summary
1151
      in
1152
      let content =
125✔
1153
        O.documentedSrc (O.keyword "class" ++ O.txt " " ++ virtual_ ++ params)
125✔
1154
        @ cname @ cd
1155
      in
1156
      let attr = [ "class" ] in
1157
      let anchor = path_to_id t.id in
1158
      let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
125✔
1159
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1160

1161
    let class_type (t : Odoc_model.Lang.ClassType.t) =
1162
      let name = Paths.Identifier.name t.id in
50✔
1163
      let params = format_params ~delim:`brackets t.params in
50✔
1164
      let virtual_ =
50✔
1165
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
6✔
1166
      in
1167
      let source_anchor = source_anchor t.source_loc in
1168
      let cname, expansion, expansion_doc =
50✔
1169
        match t.expansion with
UNCOV
1170
        | None -> (O.documentedSrc @@ O.txt name, None, None)
×
1171
        | Some csig ->
50✔
1172
            let url = Url.Path.from_identifier t.id in
1173
            let expansion_doc, items = class_signature csig in
50✔
1174
            let page =
50✔
1175
              make_expansion_page ~source_anchor url [ t.doc; expansion_doc ]
1176
                items
1177
            in
1178
            ( O.documentedSrc @@ path url [ inline @@ Text name ],
50✔
1179
              Some page,
1180
              Some expansion_doc )
1181
      in
1182
      let summary = O.txt " = " ++ class_type_expr t.expr in
50✔
1183
      let expr = attach_expansion (" = ", "object", "end") expansion summary in
50✔
1184
      let content =
50✔
1185
        O.documentedSrc
50✔
1186
          (O.keyword "class" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
50✔
1187
         ++ virtual_ ++ params ++ O.txt " ")
50✔
1188
        @ cname @ expr
1189
      in
1190
      let attr = [ "class-type" ] in
1191
      let anchor = path_to_id t.id in
1192
      let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
50✔
1193
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1194
  end
1195

1196
  open Class
1197

1198
  module Module : sig
1199
    val signature : Lang.Signature.t -> Comment.Comment.docs * Item.t list
1200
    (** Returns [header_doc, content]. *)
1201
  end = struct
1202
    let internal_module m =
1203
      let open Lang.Module in
1,493✔
1204
      match m.id.iv with
1205
      | `Module (_, name) when ModuleName.is_hidden name -> true
63✔
1206
      | _ -> false
1,430✔
1207

1208
    let internal_type t =
1209
      let open Lang.TypeDecl in
2,289✔
1210
      match t.id.iv with
1211
      | `Type (_, name) when TypeName.is_hidden name -> true
1✔
1212
      | _ -> false
2,288✔
1213

1214
    let internal_value v =
1215
      let open Lang.Value in
692✔
1216
      match v.id.iv with
1217
      | `Value (_, name) when ValueName.is_hidden name -> true
82✔
1218
      | _ -> false
610✔
1219

1220
    let internal_module_type t =
1221
      let open Lang.ModuleType in
1,028✔
1222
      match t.id.iv with
1223
      | `ModuleType (_, name) when ModuleTypeName.is_hidden name -> true
×
1224
      | _ -> false
1,028✔
1225

1226
    let internal_module_substitution t =
1227
      let open Lang.ModuleSubstitution in
12✔
1228
      match t.id.iv with
1229
      | `Module (_, name) when ModuleName.is_hidden name -> true
×
1230
      | _ -> false
12✔
1231

1232
    let internal_module_type_substitution t =
1233
      let open Lang.ModuleTypeSubstitution in
6✔
1234
      match t.id.iv with
UNCOV
1235
      | `ModuleType (_, name) when ModuleTypeName.is_hidden name -> true
×
1236
      | _ -> false
6✔
1237

1238
    let rec signature (s : Lang.Signature.t) =
1239
      let rec loop l acc_items =
2,747✔
1240
        match l with
9,521✔
1241
        | [] -> List.rev acc_items
2,747✔
1242
        | item :: rest -> (
6,774✔
1243
            let continue (item : Item.t) = loop rest (item :: acc_items) in
5,912✔
1244
            match (item : Lang.Signature.item) with
1245
            | Module (_, m) when internal_module m -> loop rest acc_items
63✔
1246
            | Type (_, t) when internal_type t -> loop rest acc_items
1✔
1247
            | Value v when internal_value v -> loop rest acc_items
82✔
UNCOV
1248
            | ModuleType m when internal_module_type m -> loop rest acc_items
×
1249
            | ModuleSubstitution m when internal_module_substitution m ->
12✔
UNCOV
1250
                loop rest acc_items
×
1251
            | ModuleTypeSubstitution m when internal_module_type_substitution m
6✔
1252
              ->
UNCOV
1253
                loop rest acc_items
×
1254
            | ModuleTypeSubstitution m -> continue @@ module_type_substitution m
6✔
1255
            | Module (_, m) -> continue @@ module_ m
1,430✔
1256
            | ModuleType m -> continue @@ module_type m
1,028✔
1257
            | Class (_, c) -> continue @@ class_ c
125✔
1258
            | ClassType (_, c) -> continue @@ class_type c
50✔
1259
            | Include m -> continue @@ include_ m
200✔
1260
            | ModuleSubstitution m -> continue @@ module_substitution m
12✔
1261
            | TypeSubstitution t ->
18✔
1262
                continue @@ type_decl ~is_substitution:true (Ordinary, t)
18✔
1263
            | Type (r, t) -> continue @@ type_decl (r, t)
2,288✔
1264
            | TypExt e -> continue @@ extension e
95✔
1265
            | Exception e -> continue @@ exn e
50✔
1266
            | Value v -> continue @@ value v
610✔
1267
            | Open o ->
62✔
1268
                let items = Sectioning.comment_items o.doc in
1269
                loop rest (List.rev_append items acc_items)
62✔
1270
            | Comment `Stop ->
43✔
1271
                let rest =
1272
                  Utils.skip_until rest ~p:(function
1273
                    | Lang.Signature.Comment `Stop -> true
37✔
1274
                    | _ -> false)
49✔
1275
                in
1276
                loop rest acc_items
43✔
1277
            | Comment (`Docs c) ->
611✔
1278
                let items = Sectioning.comment_items c in
1279
                loop rest (List.rev_append items acc_items))
611✔
1280
      in
1281
      (Lang.extract_signature_doc s, loop s.items [])
2,747✔
1282

1283
    and functor_parameter :
1284
        Odoc_model.Lang.FunctorParameter.parameter -> DocumentedSrc.t =
1285
     fun arg ->
1286
      let open Odoc_model.Lang.FunctorParameter in
167✔
1287
      let name = Paths.Identifier.name arg.id in
1288
      let render_ty = arg.expr in
167✔
1289
      let modtyp =
1290
        mty_in_decl (arg.id :> Paths.Identifier.Signature.t) render_ty
1291
      in
1292
      let modname, mod_decl =
167✔
1293
        match expansion_of_module_type_expr arg.expr with
UNCOV
1294
        | None ->
×
UNCOV
1295
            let modname = O.txt (Paths.Identifier.name arg.id) in
×
UNCOV
1296
            (modname, O.documentedSrc modtyp)
×
1297
        | Some (expansion_doc, items) ->
167✔
1298
            let url = Url.Path.from_identifier arg.id in
1299
            let modname = path url [ inline @@ Text name ] in
167✔
1300
            let type_with_expansion =
167✔
1301
              let content =
1302
                make_expansion_page ~source_anchor:None url [ expansion_doc ]
1303
                  items
1304
              in
1305
              let summary = O.render modtyp in
167✔
1306
              let status = `Default in
167✔
1307
              let expansion =
1308
                O.documentedSrc
167✔
1309
                  (O.txt Syntax.Type.annotation_separator ++ O.keyword "sig")
167✔
1310
                @ DocumentedSrc.[ Subpage { content; status } ]
1311
                @ O.documentedSrc (O.keyword "end")
167✔
1312
              in
1313
              DocumentedSrc.
1314
                [
1315
                  Alternative
1316
                    (Expansion { status = `Default; summary; url; expansion });
1317
                ]
1318
            in
1319
            (modname, type_with_expansion)
1320
      in
1321
      O.documentedSrc (O.keyword "module" ++ O.txt " ")
167✔
1322
      @ O.documentedSrc modname @ mod_decl
167✔
1323

1324
    and module_substitution (t : Odoc_model.Lang.ModuleSubstitution.t) =
1325
      let name = Paths.Identifier.name t.id in
12✔
1326
      let path = Link.from_path (t.manifest :> Paths.Path.t) in
12✔
1327
      let content =
12✔
1328
        O.documentedSrc
1329
          (O.keyword "module" ++ O.txt " " ++ O.txt name ++ O.txt " :=" ++ O.sp
12✔
1330
         ++ path)
12✔
1331
      in
1332
      let attr = [ "module-substitution" ] in
12✔
1333
      let anchor = path_to_id t.id in
1334
      let doc = Comment.to_ir t.doc in
12✔
1335
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
12✔
1336

1337
    and module_type_substitution (t : Odoc_model.Lang.ModuleTypeSubstitution.t)
1338
        =
1339
      let prefix =
6✔
1340
        O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
6✔
1341
      in
1342
      let source_anchor = None in
6✔
1343
      let modname = Paths.Identifier.name t.id in
1344
      let modname, expansion_doc, mty =
6✔
1345
        module_type_manifest ~subst:true ~source_anchor modname t.id t.doc
1346
          (Some t.manifest) prefix
1347
      in
1348
      let content =
6✔
1349
        O.documentedSrc (prefix ++ modname)
6✔
1350
        @ mty
1351
        @ O.documentedSrc
6✔
UNCOV
1352
            (if Syntax.Mod.close_tag_semicolon then O.txt ";" else O.noop)
×
1353
      in
1354
      let attr = [ "module-type" ] in
1355
      let anchor = path_to_id t.id in
1356
      let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
6✔
1357
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1358

1359
    and simple_expansion :
1360
        Odoc_model.Lang.ModuleType.simple_expansion ->
1361
        Comment.Comment.docs * Item.t list =
1362
     fun t ->
1363
      let rec extract_functor_params
2,269✔
1364
          (f : Odoc_model.Lang.ModuleType.simple_expansion) =
1365
        match f with
2,442✔
1366
        | Signature sg -> (None, sg)
2,269✔
1367
        | Functor (p, expansion) ->
173✔
1368
            let add_to params =
1369
              match p with Unit -> params | Named p -> p :: params
6✔
1370
            in
1371
            let params, sg = extract_functor_params expansion in
1372
            let params = match params with None -> [] | Some p -> p in
28✔
1373
            (Some (add_to params), sg)
173✔
1374
      in
1375
      match extract_functor_params t with
1376
      | None, sg -> signature sg
2,124✔
1377
      | Some params, sg ->
145✔
1378
          let sg_doc, content = signature sg in
1379
          let params =
145✔
1380
            Utils.flatmap params ~f:(fun arg ->
1381
                let content = functor_parameter arg in
167✔
1382
                let attr = [ "parameter" ] in
167✔
1383
                let anchor =
1384
                  Utils.option_of_result
1385
                  @@ Url.Anchor.from_identifier (arg.id :> Paths.Identifier.t)
167✔
1386
                in
1387
                let doc = [] in
167✔
1388
                [
1389
                  Item.Declaration
1390
                    { content; anchor; attr; doc; source_anchor = None };
1391
                ])
1392
          in
1393
          let prelude = mk_heading ~label:"parameters" "Parameters" :: params
145✔
1394
          and content = mk_heading ~label:"signature" "Signature" :: content in
145✔
1395
          (sg_doc, prelude @ content)
1396

1397
    and expansion_of_module_type_expr :
1398
        Odoc_model.Lang.ModuleType.expr ->
1399
        (Comment.Comment.docs * Item.t list) option =
1400
     fun t ->
1401
      let rec simple_expansion_of (t : Odoc_model.Lang.ModuleType.expr) =
2,478✔
1402
        match t with
2,651✔
1403
        | Path { p_expansion = None; _ }
285✔
1404
        | TypeOf { t_expansion = None; _ }
6✔
UNCOV
1405
        | With { w_expansion = None; _ } ->
×
1406
            None
1407
        | Path { p_expansion = Some e; _ }
338✔
1408
        | TypeOf { t_expansion = Some e; _ }
42✔
1409
        | With { w_expansion = Some e; _ } ->
165✔
1410
            Some e
1411
        | Signature sg -> Some (Signature sg)
1,642✔
1412
        | Functor (f_parameter, e) -> (
173✔
1413
            match simple_expansion_of e with
1414
            | Some e -> Some (Functor (f_parameter, e))
167✔
1415
            | None -> None)
6✔
1416
      in
1417
      match simple_expansion_of t with
1418
      | None -> None
291✔
1419
      | Some e -> Some (simple_expansion e)
2,187✔
1420

1421
    and module_ : Odoc_model.Lang.Module.t -> Item.t =
1422
     fun t ->
1423
      let modname = Paths.Identifier.name t.id in
1,430✔
1424
      let expansion =
1,430✔
1425
        match t.type_ with
1426
        | Alias (_, Some e) -> Some (simple_expansion e)
82✔
1427
        | Alias (_, None) -> None
142✔
1428
        | ModuleType e -> expansion_of_module_type_expr e
1,206✔
1429
      in
1430
      let source_anchor = source_anchor t.source_loc in
1431
      let modname, status, expansion, expansion_doc =
1,430✔
1432
        match expansion with
1433
        | None -> (O.txt modname, `Default, None, None)
244✔
1434
        | Some (expansion_doc, items) ->
1,186✔
1435
            let status =
1436
              match t.type_ with
1437
              | ModuleType (Signature _) -> `Inline
778✔
1438
              | _ -> `Default
408✔
1439
            in
1440
            let url = Url.Path.from_identifier t.id in
1441
            let link = path url [ inline @@ Text modname ] in
1,186✔
1442
            let page =
1,186✔
1443
              make_expansion_page ~source_anchor url [ t.doc; expansion_doc ]
1444
                items
1445
            in
1446
            (link, status, Some page, Some expansion_doc)
1,186✔
1447
      in
1448
      let intro = O.keyword "module" ++ O.txt " " ++ modname in
1,430✔
1449
      let summary = O.ignore intro ++ mdexpr_in_decl t.id t.type_ in
1,430✔
1450
      let modexpr =
1,430✔
1451
        attach_expansion ~status
1452
          (Syntax.Type.annotation_separator, "sig", "end")
1453
          expansion summary
1454
      in
1455
      let content =
1,430✔
1456
        O.documentedSrc intro @ modexpr
1,430✔
1457
        @ O.documentedSrc
1,430✔
UNCOV
1458
            (if Syntax.Mod.close_tag_semicolon then O.txt ";" else O.noop)
×
1459
      in
1460
      let attr = [ "module" ] in
1461
      let anchor = path_to_id t.id in
1462
      let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
1,430✔
1463
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1464

1465
    and simple_expansion_in_decl (base : Paths.Identifier.Module.t) se =
1466
      let rec ty_of_se :
82✔
1467
          Lang.ModuleType.simple_expansion -> Lang.ModuleType.expr = function
1468
        | Signature sg -> Signature sg
82✔
UNCOV
1469
        | Functor (arg, sg) -> Functor (arg, ty_of_se sg)
×
1470
      in
1471
      mty_in_decl (base :> Paths.Identifier.Signature.t) (ty_of_se se)
82✔
1472

1473
    and mdexpr_in_decl (base : Paths.Identifier.Module.t) md =
1474
      let sig_dotdotdot =
1,430✔
1475
        O.txt Syntax.Type.annotation_separator
1,430✔
1476
        ++ O.cut ++ Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
1,430✔
1477
      in
1478
      match md with
1,430✔
1479
      | Alias (_, Some se) -> simple_expansion_in_decl base se
82✔
1480
      | Alias (p, _) when not Paths.Path.(is_hidden (p :> t)) ->
142✔
1481
          O.txt " =" ++ O.sp ++ mdexpr md
142✔
UNCOV
1482
      | Alias _ -> sig_dotdotdot
×
1483
      | ModuleType mt -> mty_in_decl (base :> Paths.Identifier.Signature.t) mt
1,206✔
1484

1485
    and mdexpr : Odoc_model.Lang.Module.decl -> text = function
1486
      | Alias (mod_path, _) -> Link.from_path (mod_path :> Paths.Path.t)
184✔
UNCOV
1487
      | ModuleType mt -> mty mt
×
1488

1489
    and module_type_manifest ~subst ~source_anchor modname id doc manifest
1490
        prefix =
1491
      let expansion =
1,034✔
1492
        match manifest with
1493
        | None -> None
96✔
1494
        | Some e -> expansion_of_module_type_expr e
938✔
1495
      in
1496
      let modname, expansion, expansion_doc =
1497
        match expansion with
1498
        | None -> (O.txt modname, None, None)
285✔
1499
        | Some (expansion_doc, items) ->
749✔
1500
            let url = Url.Path.from_identifier id in
1501
            let link = path url [ inline @@ Text modname ] in
749✔
1502
            let page =
749✔
1503
              make_expansion_page ~source_anchor url [ doc; expansion_doc ]
1504
                items
1505
            in
1506
            (link, Some page, Some expansion_doc)
749✔
1507
      in
1508
      let summary =
1509
        match manifest with
1510
        | None -> O.noop
96✔
1511
        | Some expr ->
938✔
1512
            O.ignore (prefix ++ modname)
938✔
1513
            ++ (if subst then O.txt " :=" ++ O.sp else O.txt " =" ++ O.sp)
6✔
1514
            ++ mty expr
938✔
1515
      in
1516
      ( modname,
1517
        expansion_doc,
1518
        attach_expansion (" = ", "sig", "end") expansion summary )
1,034✔
1519

1520
    and module_type (t : Odoc_model.Lang.ModuleType.t) =
1521
      let prefix =
1,028✔
1522
        O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
1,028✔
1523
      in
1524
      let modname = Paths.Identifier.name t.id in
1,028✔
1525
      let source_anchor = source_anchor t.source_loc in
1,028✔
1526
      let modname, expansion_doc, mty =
1,028✔
1527
        module_type_manifest ~subst:false ~source_anchor modname t.id t.doc
1528
          t.expr prefix
1529
      in
1530
      let content =
1,028✔
1531
        O.documentedSrc (prefix ++ modname)
1,028✔
1532
        @ mty
1533
        @ O.documentedSrc
1,028✔
UNCOV
1534
            (if Syntax.Mod.close_tag_semicolon then O.txt ";" else O.noop)
×
1535
      in
1536
      let attr = [ "module-type" ] in
1537
      let anchor = path_to_id t.id in
1538
      let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
1,028✔
1539
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1540

1541
    and umty_hidden : Odoc_model.Lang.ModuleType.U.expr -> bool = function
1542
      | Path p -> Paths.Path.(is_hidden (p :> t))
287✔
1543
      | With (_, expr) -> umty_hidden expr
14✔
1544
      | TypeOf (ModPath m, _) | TypeOf (StructInclude m, _) ->
32✔
1545
          Paths.Path.(is_hidden (m :> t))
1546
      | Signature _ -> false
8✔
1547

1548
    and mty_hidden : Odoc_model.Lang.ModuleType.expr -> bool = function
1549
      | Path { p_path = mty_path; _ } -> Paths.Path.(is_hidden (mty_path :> t))
647✔
1550
      | With { w_expr; _ } -> umty_hidden w_expr
165✔
1551
      | TypeOf { t_desc = ModPath m; _ }
36✔
1552
      | TypeOf { t_desc = StructInclude m; _ } ->
12✔
1553
          Paths.Path.(is_hidden (m :> t))
1554
      | _ -> false
1,778✔
1555

1556
    and mty_with subs expr =
1557
      umty expr ++ O.sp ++ O.keyword "with" ++ O.txt " "
177✔
1558
      ++ O.list
177✔
1559
           ~sep:(O.cut ++ O.txt " " ++ O.keyword "and" ++ O.txt " ")
177✔
1560
           ~f:(fun x -> O.span (substitution x))
207✔
1561
           subs
1562

1563
    and mty_typeof t_desc =
1564
      match t_desc with
117✔
1565
      | Odoc_model.Lang.ModuleType.ModPath m ->
68✔
1566
          O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
68✔
1567
          ++ O.keyword "of" ++ O.txt " "
68✔
1568
          ++ Link.from_path (m :> Paths.Path.t)
68✔
1569
      | StructInclude m ->
49✔
1570
          O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
49✔
1571
          ++ O.keyword "of" ++ O.txt " " ++ O.keyword "struct" ++ O.txt " "
49✔
1572
          ++ O.keyword "include" ++ O.txt " "
49✔
1573
          ++ Link.from_path (m :> Paths.Path.t)
49✔
1574
          ++ O.txt " " ++ O.keyword "end"
49✔
1575

1576
    and is_elidable_with_u : Odoc_model.Lang.ModuleType.U.expr -> bool =
1577
      function
1578
      | Path _ -> false
158✔
1579
      | Signature _ -> true
2✔
UNCOV
1580
      | With (_, expr) -> is_elidable_with_u expr
×
1581
      | TypeOf _ -> false
19✔
1582

1583
    and umty : Odoc_model.Lang.ModuleType.U.expr -> text =
1584
     fun m ->
1585
      match m with
376✔
1586
      | Path p -> Link.from_path (p :> Paths.Path.t)
287✔
1587
      | Signature _ ->
6✔
1588
          Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
6✔
1589
      | With (_, expr) when is_elidable_with_u expr ->
14✔
1590
          Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
2✔
1591
      | With (subs, expr) -> mty_with subs expr
12✔
1592
      | TypeOf (t_desc, _) -> mty_typeof t_desc
69✔
1593

1594
    and mty : Odoc_model.Lang.ModuleType.expr -> text =
1595
     fun m ->
1596
      if mty_hidden m then
2,638✔
1597
        Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
×
1598
      else
1599
        match m with
2,638✔
1600
        | Path { p_path = mty_path; _ } ->
647✔
1601
            Link.from_path (mty_path :> Paths.Path.t)
UNCOV
1602
        | Functor (Unit, expr) ->
×
UNCOV
1603
            (if Syntax.Mod.functor_keyword then O.keyword "functor" else O.noop)
×
UNCOV
1604
            ++ O.span (O.txt " () " ++ Syntax.Type.arrow)
×
UNCOV
1605
            ++ O.sp ++ mty expr
×
1606
        | Functor (Named arg, expr) ->
42✔
1607
            let arg_expr = arg.expr in
1608
            let stop_before = expansion_of_module_type_expr arg_expr = None in
42✔
1609
            let name =
1610
              let open Odoc_model.Lang.FunctorParameter in
1611
              let name = Paths.Identifier.name arg.id in
1612
              match
42✔
1613
                Url.from_identifier ~stop_before (arg.id :> Paths.Identifier.t)
1614
              with
UNCOV
1615
              | Error _ -> O.txt name
×
1616
              | Ok href -> resolved href [ inline @@ Text name ]
42✔
1617
            in
UNCOV
1618
            (if Syntax.Mod.functor_keyword then O.keyword "functor" else O.noop)
×
1619
            ++ (O.box_hv @@ O.span
42✔
1620
               @@ O.txt " (" ++ name
42✔
1621
                  ++ O.txt Syntax.Type.annotation_separator
42✔
1622
                  ++ mty arg_expr ++ O.txt ")" ++ O.txt " " ++ Syntax.Type.arrow
42✔
1623
               )
1624
            ++ O.sp ++ mty expr
42✔
1625
        | With { w_expr; _ } when is_elidable_with_u w_expr ->
165✔
UNCOV
1626
            Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
×
1627
        | With { w_substitutions; w_expr; _ } ->
165✔
1628
            O.box_hv @@ mty_with w_substitutions w_expr
165✔
1629
        | TypeOf { t_desc; _ } -> mty_typeof t_desc
48✔
1630
        | Signature _ ->
1,736✔
1631
            Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
1,736✔
1632

1633
    and mty_in_decl :
1634
        Paths.Identifier.Signature.t -> Odoc_model.Lang.ModuleType.expr -> text
1635
        =
1636
     fun base -> function
1637
      | (Path _ | Signature _ | With _ | TypeOf _) as m ->
30✔
1638
          O.txt Syntax.Type.annotation_separator ++ O.cut ++ mty m
1,455✔
1639
      | Functor _ as m when not Syntax.Mod.functor_contraction ->
131✔
UNCOV
1640
          O.txt Syntax.Type.annotation_separator ++ O.cut ++ mty m
×
1641
      | Functor (arg, expr) ->
131✔
1642
          let text_arg =
1643
            match arg with
1644
            | Unit -> O.txt "()"
6✔
1645
            | Named arg ->
125✔
1646
                let arg_expr = arg.expr in
1647
                let stop_before =
1648
                  expansion_of_module_type_expr arg_expr = None
125✔
1649
                in
1650
                let name =
1651
                  let open Odoc_model.Lang.FunctorParameter in
1652
                  let name = Paths.Identifier.name arg.id in
1653
                  match
125✔
1654
                    Url.from_identifier ~stop_before
1655
                      (arg.id :> Paths.Identifier.t)
1656
                  with
UNCOV
1657
                  | Error _ -> O.txt name
×
1658
                  | Ok href -> resolved href [ inline @@ Text name ]
125✔
1659
                in
1660
                O.box_hv
125✔
1661
                @@ O.txt "(" ++ name
125✔
1662
                   ++ O.txt Syntax.Type.annotation_separator
125✔
1663
                   ++ O.cut ++ mty arg.expr ++ O.txt ")"
125✔
1664
          in
1665
          O.sp ++ text_arg ++ mty_in_decl base expr
131✔
1666

1667
    (* TODO : Centralize the list juggling for type parameters *)
1668
    and type_expr_in_subst td typath =
1669
      let typath = Link.from_fragment typath in
110✔
1670
      match td.Lang.TypeDecl.Equation.params with
110✔
1671
      | [] -> typath
92✔
1672
      | l -> Syntax.Type.handle_substitution_params typath (format_params l)
18✔
1673

1674
    and substitution : Odoc_model.Lang.ModuleType.substitution -> text =
1675
      function
1676
      | ModuleEq (frag_mod, md) ->
42✔
1677
          O.box_hv
1678
          @@ O.keyword "module" ++ O.txt " "
42✔
1679
             ++ Link.from_fragment (frag_mod :> Paths.Fragment.leaf)
42✔
1680
             ++ O.txt " =" ++ O.sp ++ mdexpr md
42✔
1681
      | ModuleTypeEq (frag_mty, md) ->
24✔
1682
          O.box_hv
1683
          @@ O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
24✔
1684
             ++ Link.from_fragment (frag_mty :> Paths.Fragment.leaf)
24✔
1685
             ++ O.txt " =" ++ O.sp ++ mty md
24✔
1686
      | TypeEq (frag_typ, td) ->
78✔
1687
          O.box_hv
1688
          @@ O.keyword "type" ++ O.txt " "
78✔
1689
             ++ type_expr_in_subst td (frag_typ :> Paths.Fragment.leaf)
78✔
1690
             ++ fst (format_manifest td)
78✔
1691
             ++ format_constraints
78✔
1692
                  td.Odoc_model.Lang.TypeDecl.Equation.constraints
1693
      | ModuleSubst (frag_mod, mod_path) ->
19✔
1694
          O.box_hv
1695
          @@ O.keyword "module" ++ O.txt " "
19✔
1696
             ++ Link.from_fragment (frag_mod :> Paths.Fragment.leaf)
19✔
1697
             ++ O.txt " :=" ++ O.sp
19✔
1698
             ++ Link.from_path (mod_path :> Paths.Path.t)
19✔
1699
      | ModuleTypeSubst (frag_mty, md) ->
12✔
1700
          O.box_hv
1701
          @@ O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
12✔
1702
             ++ Link.from_fragment (frag_mty :> Paths.Fragment.leaf)
12✔
1703
             ++ O.txt " :=" ++ O.sp ++ mty md
12✔
1704
      | TypeSubst (frag_typ, td) -> (
32✔
1705
          O.box_hv
1706
          @@ O.keyword "type" ++ O.txt " "
32✔
1707
             ++ type_expr_in_subst td (frag_typ :> Paths.Fragment.leaf)
32✔
1708
             ++ O.txt " :=" ++ O.sp
32✔
1709
             ++
32✔
1710
             match td.Lang.TypeDecl.Equation.manifest with
1711
             | None -> assert false (* cf loader/cmti *)
1712
             | Some te -> type_expr te)
32✔
1713

1714
    and include_ (t : Odoc_model.Lang.Include.t) =
1715
      let decl_hidden =
200✔
1716
        match t.decl with
UNCOV
1717
        | Alias p -> Paths.Path.(is_hidden (p :> t))
×
1718
        | ModuleType mty -> umty_hidden mty
200✔
1719
      in
1720
      let status = if decl_hidden then `Inline else t.status in
1✔
1721

1722
      let _, content = signature t.expansion.content in
1723
      let summary =
200✔
1724
        if decl_hidden then O.render (O.keyword "include" ++ O.txt " ...")
1✔
1725
        else
1726
          let include_decl =
199✔
1727
            match t.decl with
1728
            | Odoc_model.Lang.Include.Alias mod_path ->
×
UNCOV
1729
                Link.from_path (mod_path :> Paths.Path.t)
×
1730
            | ModuleType mt -> umty mt
199✔
1731
          in
1732
          O.render
199✔
1733
            (O.keyword "include" ++ O.txt " " ++ include_decl
199✔
UNCOV
1734
            ++ if Syntax.Mod.include_semicolon then O.keyword ";" else O.noop)
×
1735
      in
1736
      let content = { Include.content; status; summary } in
1737
      let attr = [ "include" ] in
1738
      let anchor = None in
1739
      let doc =
1740
        (* Documentation attached to includes behave differently than other
1741
           declarations, which show only the synopsis. We can't only show the
1742
           synopsis because no page is generated to render it and we'd loose
1743
           the full documentation.
1744
           The documentation from the expansion is not used. *)
1745
        Comment.to_ir t.doc
1746
      in
1747
      Item.Include { attr; anchor; doc; content; source_anchor = None }
200✔
1748
  end
1749

1750
  open Module
1751

1752
  module Page : sig
1753
    val compilation_unit : Lang.Compilation_unit.t -> Document.t
1754

1755
    val page : Lang.Page.t -> Document.t
1756

1757
    val source_tree : Lang.SourceTree.t -> Document.t list
1758

1759
    val implementation :
1760
      Lang.Implementation.t ->
1761
      Syntax_highlighter.infos ->
1762
      string ->
1763
      Document.t list
1764
  end = struct
1765
    let pack : Lang.Compilation_unit.Packed.t -> Item.t list =
1766
     fun t ->
UNCOV
1767
      let f x =
×
1768
        let id = x.Lang.Compilation_unit.Packed.id in
×
1769
        let modname = Paths.Identifier.name id in
UNCOV
1770
        let md_def =
×
1771
          O.keyword "module" ++ O.txt " " ++ O.txt modname ++ O.txt " = "
×
UNCOV
1772
          ++ Link.from_path (x.path :> Paths.Path.t)
×
1773
        in
UNCOV
1774
        let content = O.documentedSrc md_def in
×
UNCOV
1775
        let anchor =
×
1776
          Utils.option_of_result
UNCOV
1777
          @@ Url.Anchor.from_identifier (id :> Paths.Identifier.t)
×
1778
        in
UNCOV
1779
        let attr = [ "modules" ] in
×
1780
        let doc = [] in
1781
        let decl = { Item.anchor; content; attr; doc; source_anchor = None } in
1782
        Item.Declaration decl
1783
      in
1784
      List.map f t
1785

1786
    let compilation_unit (t : Odoc_model.Lang.Compilation_unit.t) =
1787
      let url = Url.Path.from_identifier t.id in
278✔
1788
      let unit_doc, items =
278✔
1789
        match t.content with
1790
        | Module sign -> signature sign
278✔
UNCOV
1791
        | Pack packed -> ([], pack packed)
×
1792
      in
1793
      let source_anchor = source_anchor t.source_loc in
1794
      let page = make_expansion_page ~source_anchor url [ unit_doc ] items in
278✔
1795
      Document.Page page
278✔
1796

1797
    let page (t : Odoc_model.Lang.Page.t) =
1798
      (*let name =
1799
          match t.name.iv with `Page (_, name) | `LeafPage (_, name) -> name
1800
        in*)
1801
      (*let title = Odoc_model.Names.PageName.to_string name in*)
1802
      let url = Url.Path.from_identifier t.name in
42✔
1803
      let preamble, items = Sectioning.docs t.content in
42✔
1804
      let source_anchor = None in
42✔
1805
      Document.Page { Page.preamble; items; url; source_anchor }
1806

1807
    let source_tree t =
UNCOV
1808
      let dir_pages = t.Odoc_model.Lang.SourceTree.source_children in
×
1809
      let open Paths.Identifier in
1810
      let module Set = Set.Make (SourceDir) in
1811
      let module M = Map.Make (SourceDir) in
1812
      (* mmap is a from a [SourceDir.t] to its [SourceDir.t] and [SourcePage.t]
1813
         children *)
1814
      let mmap =
1815
        let add parent f mmap =
UNCOV
1816
          let old_value =
×
1817
            try M.find parent mmap with Not_found -> (Set.empty, [])
×
1818
          in
1819
          M.add parent (f old_value) mmap
×
1820
        and add_file file (set, lp) = (set, file :: lp)
×
1821
        and add_dir dir (set, lp) = (Set.add dir set, lp) in
×
1822
        let rec dir_ancestors_add dir mmap =
UNCOV
1823
          match dir.iv with
×
UNCOV
1824
          | `SourceDir (parent, _) ->
×
1825
              let mmap = add parent (add_dir dir) mmap in
×
1826
              dir_ancestors_add parent mmap
×
UNCOV
1827
          | `Page _ -> mmap
×
1828
        in
1829
        let file_ancestors_add ({ iv = `SourcePage (parent, _); _ } as file)
1830
            mmap =
UNCOV
1831
          let mmap = add parent (add_file file) mmap in
×
UNCOV
1832
          dir_ancestors_add parent mmap
×
1833
        in
1834
        List.fold_left
×
1835
          (fun mmap file -> file_ancestors_add file mmap)
×
1836
          M.empty dir_pages
1837
      in
1838
      let page_of_dir (dir : SourceDir.t) (dir_children, file_children) =
UNCOV
1839
        let url = Url.Path.from_identifier dir in
×
UNCOV
1840
        let block ?(attr = []) desc = Block.{ attr; desc } in
×
1841
        let inline ?(attr = []) desc = Inline.[ { attr; desc } ] in
×
1842
        let header =
1843
          let title = inline (Text (name dir)) in
×
UNCOV
1844
          Item.Heading
×
1845
            Heading.{ label = None; level = 0; title; source_anchor = None }
1846
        in
1847
        let li ?(attr = []) name url =
×
UNCOV
1848
          let link url desc =
×
UNCOV
1849
            let content = [ Inline.{ attr = []; desc } ] and tooltip = None in
×
1850
            Inline.InternalLink
1851
              { InternalLink.target = Resolved url; content; tooltip }
1852
          in
1853
          [ block ~attr @@ Block.Inline (inline @@ link url (Text name)) ]
×
1854
        in
1855
        let li_of_child child =
UNCOV
1856
          match child with
×
1857
          | { iv = `Page _; _ } ->
1858
              assert false (* No [`Page] is child of a [`SourceDir] *)
1859
          | { iv = `SourceDir (_, name); _ } ->
×
UNCOV
1860
              let url = child |> Url.Path.from_identifier |> Url.from_path in
×
UNCOV
1861
              (name, url)
×
1862
        in
1863
        let li_of_file_child ({ iv = `SourcePage (_, name); _ } as child) =
UNCOV
1864
          let url = child |> Url.Path.from_identifier |> Url.from_path in
×
UNCOV
1865
          (name, url)
×
1866
        in
1867
        let items =
UNCOV
1868
          let text ?(attr = []) desc = Item.Text [ { attr; desc } ] in
×
UNCOV
1869
          let list l = Block.List (Block.Unordered, l) in
×
1870
          let list_of_children =
1871
            let dir_list =
1872
              Set.fold
×
1873
                (fun child acc -> li_of_child child :: acc)
×
1874
                dir_children []
1875
            and file_list =
UNCOV
1876
              List.map (fun child -> li_of_file_child child) file_children
×
1877
            in
1878
            let sort ?(attr = []) l =
×
UNCOV
1879
              l
×
UNCOV
1880
              |> List.sort (fun (n1, _) (n2, _) -> String.compare n1 n2)
×
1881
              |> List.map (fun (name, url) -> li ~attr name url)
×
1882
            in
UNCOV
1883
            sort ~attr:[ "odoc-directory" ] dir_list
×
UNCOV
1884
            @ sort ~attr:[ "odoc-file" ] file_list
×
1885
          in
1886
          header
UNCOV
1887
          :: [ text ~attr:[ "odoc-folder-list" ] @@ list list_of_children ]
×
1888
        in
1889
        Document.Page
1890
          { Types.Page.preamble = []; items; url; source_anchor = None }
1891
      in
UNCOV
1892
      M.fold (fun dir children acc -> page_of_dir dir children :: acc) mmap []
×
1893

1894
    let implementation (v : Odoc_model.Lang.Implementation.t) syntax_info
1895
        source_code =
1896
      match v.id with
26✔
UNCOV
1897
      | None -> []
×
1898
      | Some id ->
26✔
1899
          [
1900
            Document.Source_page
1901
              (Source_page.source id syntax_info v.source_info source_code);
26✔
1902
          ]
1903
  end
1904

1905
  include Page
1906

1907
  let type_expr = type_expr
1908

1909
  let record = record
1910
end
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