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

ocaml / odoc / 2994

09 Jul 2025 05:27PM UTC coverage: 73.054% (-0.06%) from 73.118%
2994

Pull #1362

github

web-flow
Merge 158fd7cb3 into 64ef0eb66
Pull Request #1362: Voodoo occurrences

10373 of 14199 relevant lines covered (73.05%)

7148.43 hits per line

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

86.03
/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_utils
18
open Odoc_model.Names
19
module Location = Odoc_model.Location_
20
module Paths = Odoc_model.Paths
21
open Types
22
module O = Codefmt
23
open O.Infix
24

25
let tag tag t = O.span ~attr:tag t
13,399✔
26

27
let label t =
28
  match t with
3,263✔
29
  | Odoc_model.Lang.TypeExpr.Label s -> tag "label" (O.txt s)
574✔
30
  | Optional s | RawOptional s -> tag "optlabel" (O.txt "?" ++ O.txt s)
1✔
31

32
let type_var tv = tag "type-var" (O.txt tv)
9,479✔
33

34
let enclose ~l ~r x = O.span (O.txt l ++ x ++ O.txt r)
14,345✔
35

36
let resolved p content =
37
  let link = { Link.target = Internal (Resolved p); content; tooltip = None } in
159,728✔
38
  O.elt [ inline @@ Link link ]
159,728✔
39

40
let path p content = resolved (Url.from_path p) content
2,936✔
41

42
let unresolved content =
43
  let link = { Link.target = Internal Unresolved; content; tooltip = None } in
582✔
44
  O.elt [ inline @@ Link link ]
582✔
45

46
let path_to_id path =
47
  let url = Url.Anchor.from_identifier (path :> Paths.Identifier.t) in
7,466✔
48
  Some url
7,466✔
49

50
let source_anchor source_loc =
51
  match source_loc with
7,819✔
52
  | Some id ->
104✔
53
      Some
54
        (Url.Anchor.from_identifier
104✔
55
           (id : Paths.Identifier.SourceLocation.t :> Paths.Identifier.t))
56
  | _ -> None
7,715✔
57

58
let attach_expansion ?(status = `Default) (eq, o, e) page text =
1,583✔
59
  match page with
3,426✔
60
  | None -> O.documentedSrc text
701✔
61
  | Some (page : Page.t) ->
2,725✔
62
      let url = page.url in
63
      let summary = O.render text in
64
      let expansion =
2,725✔
65
        O.documentedSrc (O.txt eq ++ O.keyword o)
2,725✔
66
        @ DocumentedSrc.[ Subpage { status; content = page } ]
67
        @ O.documentedSrc (O.keyword e)
2,725✔
68
      in
69
      DocumentedSrc.
70
        [ Alternative (Expansion { summary; url; status; expansion }) ]
71

72
let mk_heading ?(level = 1) ?label text =
366✔
73
  let title = [ inline @@ Text text ] in
366✔
74
  Item.Heading { label; level; title; source_anchor = None }
75

76
(** Returns the preamble as an item. Stop the preamble at the first heading. The
77
    rest is inserted into [items]. *)
78
let prepare_preamble comment items =
79
  let preamble, first_comment =
3,286✔
80
    List.split_at
81
      ~f:(function
82
        | { Odoc_model.Location_.value = `Heading _; _ } -> true | _ -> false)
32✔
83
      comment
84
  in
85
  (Comment.standalone preamble, Comment.standalone first_comment @ items)
3,286✔
86

87
let make_expansion_page ~source_anchor url comments items =
88
  let comment = List.concat comments in
3,286✔
89
  let preamble, items = prepare_preamble comment items in
3,286✔
90
  { Page.preamble; items; url; source_anchor }
3,286✔
91

92
include Generator_signatures
93

94
module Make (Syntax : SYNTAX) = struct
95
  module Link : sig
96
    val from_path : Paths.Path.t -> text
97

98
    val from_fragment : Paths.Fragment.leaf -> text
99
  end = struct
100
    open Paths
101

102
    let rec from_path : Path.t -> text =
103
     fun path ->
104
      match path with
181,884✔
105
      | `Identifier (id, _) ->
245✔
106
          unresolved [ inline @@ Text (Identifier.name id) ]
245✔
107
      | `Substituted m -> from_path (m :> Path.t)
×
108
      | `SubstitutedMT m -> from_path (m :> Path.t)
×
109
      | `SubstitutedT m -> from_path (m :> Path.t)
×
110
      | `SubstitutedCT m -> from_path (m :> Path.t)
×
111
      | `Root root -> unresolved [ inline @@ Text (ModuleName.to_string root) ]
305✔
112
      | `Forward root -> unresolved [ inline @@ Text root ] (* FIXME *)
×
113
      | `Dot (prefix, suffix) ->
305✔
114
          let link = from_path (prefix :> Path.t) in
115
          link ++ O.txt ("." ^ ModuleName.to_string suffix)
305✔
116
      | `DotT (prefix, suffix) ->
297✔
117
          let link = from_path (prefix :> Path.t) in
118
          link ++ O.txt ("." ^ TypeName.to_string suffix)
297✔
119
      | `DotMT (prefix, suffix) ->
×
120
          let link = from_path (prefix :> Path.t) in
121
          link ++ O.txt ("." ^ ModuleTypeName.to_string suffix)
×
122
      | `DotV (prefix, suffix) ->
×
123
          let link = from_path (prefix :> Path.t) in
124
          link ++ O.txt ("." ^ ValueName.to_string suffix)
×
125
      | `Apply (p1, p2) ->
×
126
          let link1 = from_path (p1 :> Path.t) in
127
          let link2 = from_path (p2 :> Path.t) in
×
128
          link1 ++ O.txt "(" ++ link2 ++ O.txt ")"
×
129
      | `Resolved _ when Paths.Path.is_hidden path ->
180,732✔
130
          let txt = Url.render_path path in
32✔
131
          unresolved [ inline @@ Text txt ]
32✔
132
      | `Resolved rp -> (
180,700✔
133
          (* If the path is pointing to an opaque module or module type
134
             there won't be a page generated - so we stop before; at
135
             the parent page, and link instead to the anchor representing
136
             the declaration of the opaque module(_type) *)
137
          let stop_before =
138
            match rp with
139
            | `OpaqueModule _ | `OpaqueModuleType _ -> true
8✔
140
            | _ -> false
180,492✔
141
          in
142
          let txt = [ inline @@ Text (Url.render_path path) ] in
180,700✔
143
          match Paths.Path.Resolved.identifier rp with
144
          | Some id ->
156,291✔
145
              let href = Url.from_identifier ~stop_before id in
146
              resolved href txt
156,291✔
147
          | None -> O.elt txt)
24,409✔
148

149
    let dot prefix suffix = prefix ^ "." ^ suffix
49✔
150

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

160
    and render_resolved_fragment : Fragment.Resolved.t -> string =
161
      let open Fragment.Resolved in
162
      fun fragment ->
163
        match fragment with
371✔
164
        | `Root _ -> assert false
165
        | `Subst (_, rr) -> render_resolved_fragment (rr :> t)
8✔
166
        | `Alias (_, rr) -> render_resolved_fragment (rr :> t)
24✔
167
        | `Module (`Root _, s) -> ModuleName.to_string s
121✔
168
        | `Module_type (`Root _, s) -> ModuleTypeName.to_string s
32✔
169
        | `Type (`Root _, s) -> TypeName.to_string s
137✔
170
        | `Class (`Root _, s) -> TypeName.to_string s
×
171
        | `ClassType (`Root _, s) -> TypeName.to_string s
×
172
        | `Module (rr, s) ->
8✔
173
            dot (render_resolved_fragment (rr :> t)) (ModuleName.to_string s)
8✔
174
        | `Module_type (rr, s) ->
16✔
175
            dot
176
              (render_resolved_fragment (rr :> t))
16✔
177
              (ModuleTypeName.to_string s)
16✔
178
        | `Type (rr, s) ->
25✔
179
            dot (render_resolved_fragment (rr :> t)) (TypeName.to_string s)
25✔
180
        | `Class (rr, s) ->
×
181
            dot (render_resolved_fragment (rr :> t)) (TypeName.to_string s)
×
182
        | `ClassType (rr, s) ->
×
183
            dot (render_resolved_fragment (rr :> t)) (TypeName.to_string s)
×
184
        | `OpaqueModule r -> render_resolved_fragment (r :> t)
×
185

186
    let resolved_fragment_to_ir : Fragment.Resolved.leaf -> text =
187
     fun fragment ->
188
      let open Fragment in
290✔
189
      let id = Resolved.identifier (fragment :> Resolved.t) in
190
      let txt = render_resolved_fragment (fragment :> Resolved.t) in
290✔
191
      let href = Url.from_identifier ~stop_before:false id in
290✔
192
      resolved href [ inline @@ Text txt ]
290✔
193

194
    let from_fragment : Fragment.leaf -> text = function
195
      | `Resolved r
290✔
196
        when not (Fragment.Resolved.is_hidden (r :> Fragment.Resolved.t)) ->
290✔
197
          resolved_fragment_to_ir r
290✔
198
      | f ->
×
199
          let txt = render_fragment_any (f :> Fragment.t) in
200
          unresolved [ inline @@ Text txt ]
×
201
  end
202

203
  module Impl = struct
204
    let impl ~infos src =
205
      let l =
28✔
206
        infos
207
        |> List.sort (fun (_, (l1, e1)) (_, (l2, e2)) ->
208
               if l1 = l2 then compare e2 e1
133✔
209
                 (* If two intervals open at the same time, we open
210
                    first the one that closes last *)
211
               else compare l1 l2)
3,166✔
212
      in
213
      let get_src a b =
28✔
214
        let in_bound x = min (max x 0) (String.length src) in
1,696✔
215
        let a = in_bound a and b = in_bound b in
1,696✔
216
        let a, b = (min a b, max a b) in
1,696✔
217
        String.with_range src ~first:a ~len:(b - a)
218
      in
219
      let plain_code = function
220
        | "" -> []
596✔
221
        | s -> [ Types.Source_page.Plain_code s ]
1,100✔
222
      in
223
      let min (a : int) b = if a < b then a else b in
161✔
224
      let rec extract from to_ list aux =
225
        match list with
1,696✔
226
        | (k, (loc_start, loc_end)) :: q when loc_start < to_ ->
1,640✔
227
            let loc_end = min loc_end to_ in
834✔
228
            (* In case of inconsistent [a  [b    a] b]
229
               we do                   [a  [b  b]a] *)
230
            let initial = plain_code (get_src from loc_start) in
834✔
231
            let next, q = extract loc_start loc_end q [] in
834✔
232
            extract loc_end to_ q
834✔
233
              ([ Types.Source_page.Tagged_code (k, List.rev next) ]
834✔
234
              @ initial @ aux)
235
        | q -> (plain_code (get_src from to_) @ aux, q)
862✔
236
      in
237
      let doc, _ = extract 0 (String.length src) l [] in
28✔
238
      List.rev doc
28✔
239
  end
240

241
  module Source_page : sig
242
    val source :
243
      Paths.Identifier.SourcePage.t ->
244
      Syntax_highlighter.infos ->
245
      Lang.Source_info.t ->
246
      string ->
247
      Source_page.t
248
  end = struct
249
    let path id = Url.Path.from_identifier id
28✔
250

251
    let to_link { Lang.Source_info.documentation; implementation } =
252
      let documentation =
34✔
253
        (* Since documentation link are not rendered, we comment the code to
254
           extract the href, and always output [None] *)
255
        ignore documentation;
256
        None
257
        (* let open Paths.Path.Resolved in *)
258
        (* match documentation with *)
259
        (* | Some (`Resolved p) when not (is_hidden (p :> t)) -> ( *)
260
        (*     let id = identifier (p :> t) in *)
261
        (*     match Url.from_identifier ~stop_before:false id with *)
262
        (*     | Ok link -> Some link *)
263
        (*     | _ -> None) *)
264
        (* | _ -> None *)
265
      in
266
      let implementation =
267
        match implementation with
268
        | Some (Odoc_model.Lang.Source_info.Resolved id) ->
15✔
269
            Some (Url.Anchor.from_identifier (id :> Paths.Identifier.t))
15✔
270
        | _ -> None
19✔
271
      in
272
      Some (Source_page.Link { implementation; documentation })
273

274
    let info_of_info : Lang.Source_info.annotation -> Source_page.info option =
275
      function
276
      | Definition id -> (
99✔
277
          match id.iv with
278
          | `SourceLocation (_, def) -> Some (Anchor (DefName.to_string def))
95✔
279
          | `SourceLocationInternal (_, local) ->
4✔
280
              Some (Anchor (LocalName.to_string local))
4✔
281
          | _ -> None)
×
282
      | Module v -> to_link v
11✔
283
      | ModuleType v -> to_link v
1✔
284
      | Type v -> to_link v
7✔
285
      | Value v -> to_link v
15✔
286

287
    let source id syntax_info infos source_code =
288
      let url = path id in
28✔
289
      let mapper (info, loc) =
28✔
290
        match info_of_info info with Some x -> Some (x, loc) | None -> None
×
291
      in
292
      let infos = Odoc_utils.List.filter_map mapper infos in
293
      let syntax_info =
28✔
294
        List.rev_map (fun (ty, loc) -> (Source_page.Syntax ty, loc)) syntax_info
701✔
295
        |> List.rev
28✔
296
      in
297
      let contents = Impl.impl ~infos:(infos @ syntax_info) source_code in
28✔
298
      { Source_page.url; contents }
28✔
299
  end
300

301
  module Type_expression : sig
302
    val type_expr : ?needs_parentheses:bool -> Lang.TypeExpr.t -> text
303

304
    val format_type_path :
305
      delim:[ `parens | `brackets ] -> Lang.TypeExpr.t list -> text -> text
306
  end = struct
307
    let rec te_variant (t : Odoc_model.Lang.TypeExpr.Polymorphic_variant.t) =
308
      let style_arguments ~constant arguments =
75,143✔
309
        (* Multiple arguments in a polymorphic variant constructor correspond
310
           to a conjunction of types, not a product: [`Lbl int&float].
311
           If constant is [true], the conjunction starts with an empty type,
312
           for instance [`Lbl &int].
313
        *)
314
        let wrapped_type_expr =
1,873✔
315
          (* type conjunction in Reason is printed as `Lbl (t1)&(t2)` *)
316
          if Syntax.Type.Variant.parenthesize_params then fun x ->
×
317
            enclose ~l:"(" ~r:")" (type_expr x)
×
318
          else fun x -> type_expr x
1,873✔
319
        in
320
        let arguments =
321
          O.list arguments ~sep:(O.txt " & ") ~f:wrapped_type_expr
1,873✔
322
        in
323
        if constant then O.txt "& " ++ arguments else arguments
×
324
      in
325
      let rec style_elements ~add_pipe = function
326
        | [] -> O.noop
75,143✔
327
        | first :: rest ->
108,795✔
328
            let first =
329
              match first with
330
              | Odoc_model.Lang.TypeExpr.Polymorphic_variant.Type te ->
40,832✔
331
                  let res = O.box_hv @@ type_expr te in
40,832✔
332
                  if add_pipe then O.sp ++ O.span (O.txt "| " ++ res) else res
2,565✔
333
              | Constructor { constant; name; arguments; _ } ->
67,963✔
334
                  let constr =
335
                    let name = "`" ^ name in
336
                    if add_pipe then O.span (O.txt ("| " ^ name))
31,095✔
337
                    else O.txt name
36,868✔
338
                  in
339
                  let res =
340
                    O.box_hv
341
                      (match arguments with
342
                      | [] -> constr
66,090✔
343
                      | _ ->
1,873✔
344
                          let arguments = style_arguments ~constant arguments in
345
                          O.span
1,873✔
346
                            (if Syntax.Type.Variant.parenthesize_params then
347
                               constr ++ arguments
×
348
                             else constr ++ O.txt " of" ++ O.sp ++ arguments))
1,873✔
349
                  in
350
                  if add_pipe then O.sp ++ res else res
31,095✔
351
            in
352
            first ++ style_elements ~add_pipe:true rest
108,795✔
353
      in
354
      let elements = style_elements ~add_pipe:false t.elements in
355
      O.box_hv_no_indent
75,143✔
356
      @@ O.span
75,143✔
357
           (match t.kind with
358
           | Fixed -> O.txt "[ " ++ elements ++ O.txt " ]"
7,068✔
359
           | Open -> O.txt "[> " ++ elements ++ O.txt " ]"
40,908✔
360
           | Closed [] -> O.txt "[< " ++ elements ++ O.txt " ]"
27,132✔
361
           | Closed lst ->
35✔
362
               let constrs = String.concat ~sep:" " lst in
363
               O.txt "[< " ++ elements ++ O.txt (" " ^ constrs ^ " ]"))
35✔
364

365
    and te_object (t : Odoc_model.Lang.TypeExpr.Object.t) =
366
      let fields =
80✔
367
        O.list
368
          ~sep:(O.sp ++ O.txt Syntax.Obj.field_separator)
80✔
369
          t.fields
370
          ~f:(function
371
            | Odoc_model.Lang.TypeExpr.Object.Method { name; type_ } ->
120✔
372
                O.box_hv_no_indent
373
                @@ O.txt (name ^ Syntax.Type.annotation_separator)
120✔
374
                   ++ O.cut ++ type_expr type_
120✔
375
            | Inherit type_ -> O.box_hv_no_indent @@ type_expr type_)
×
376
      in
377
      let open_tag =
80✔
378
        if t.open_ then O.txt Syntax.Obj.open_tag_extendable
32✔
379
        else O.txt Syntax.Obj.open_tag_closed
48✔
380
      in
381
      let close_tag =
382
        if t.open_ then O.txt Syntax.Obj.close_tag_extendable
32✔
383
        else O.txt Syntax.Obj.close_tag_closed
48✔
384
      in
385
      O.span (open_tag ++ fields ++ close_tag)
80✔
386

387
    and format_type_path ~delim (params : Odoc_model.Lang.TypeExpr.t list)
388
        (path : text) : text =
389
      O.box_hv
179,484✔
390
      @@
391
      match params with
392
      | [] -> path
94,841✔
393
      | [ param ] ->
71,284✔
394
          let param = type_expr ~needs_parentheses:true param in
395
          let args =
71,284✔
396
            if Syntax.Type.parenthesize_constructor then
397
              O.txt "(" ++ param ++ O.txt ")"
×
398
            else param
71,284✔
399
          in
400
          Syntax.Type.handle_constructor_params path args
71,284✔
401
      | params ->
13,359✔
402
          let params = O.list params ~sep:(O.txt "," ++ O.sp) ~f:type_expr in
13,359✔
403
          let params =
13,359✔
404
            match delim with
405
            | `parens -> enclose ~l:"(" params ~r:")"
13,359✔
406
            | `brackets -> enclose ~l:"[" params ~r:"]"
×
407
          in
408
          Syntax.Type.handle_constructor_params path (O.box_hv params)
13,359✔
409

410
    and type_expr ?(needs_parentheses = false) (t : Odoc_model.Lang.TypeExpr.t)
191,585✔
411
        =
412
      let enclose_parens_if_needed res =
312,049✔
413
        if needs_parentheses then enclose ~l:"(" res ~r:")" else res
32✔
414
      in
415
      match t with
416
      | Var s -> type_var (Syntax.Type.var_prefix ^ s)
9,461✔
417
      | Any -> type_var Syntax.Type.any
18✔
418
      | Alias (te, alias) ->
133✔
419
          enclose_parens_if_needed
420
            (type_expr ~needs_parentheses:true te
133✔
421
            ++ O.txt " " ++ O.keyword "as" ++ O.txt " '" ++ O.txt alias)
133✔
422
      | Arrow (None, src, dst) ->
43,800✔
423
          let res =
424
            O.span
43,800✔
425
              ((O.box_hv @@ type_expr ~needs_parentheses:true src)
43,800✔
426
              ++ O.txt " " ++ Syntax.Type.arrow)
43,800✔
427
            ++ O.sp ++ type_expr dst
43,800✔
428
            (* ++ O.end_hv *)
429
          in
430
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
783✔
431
      | Arrow (Some (RawOptional _ as lbl), _src, dst) ->
1✔
432
          let res =
433
            O.span
1✔
434
              (O.box_hv
1✔
435
              @@ label lbl ++ O.txt ":"
1✔
436
                 ++ tag "error" (O.txt "???")
1✔
437
                 ++ O.txt " " ++ Syntax.Type.arrow)
1✔
438
            ++ O.sp ++ type_expr dst
1✔
439
          in
440
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
×
441
      | Arrow (Some lbl, src, dst) ->
3,262✔
442
          let res =
443
            O.span
3,262✔
444
              ((O.box_hv
3,262✔
445
               @@ label lbl ++ O.txt ":" ++ O.cut
3,262✔
446
                  ++ (O.box_hv @@ type_expr ~needs_parentheses:true src))
3,262✔
447
              ++ O.txt " " ++ Syntax.Type.arrow)
3,262✔
448
            ++ O.sp ++ type_expr dst
3,262✔
449
          in
450
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
16✔
451
      | Tuple lst ->
677✔
452
          let res =
453
            O.box_hv_no_indent
454
              (O.list lst ~sep:Syntax.Type.Tuple.element_separator
677✔
455
                 ~f:(fun (lbl, ty) ->
456
                   match lbl with
1,544✔
457
                   | None -> type_expr ~needs_parentheses:true ty
1,544✔
458
                   | Some lbl ->
×
459
                       tag "label" (O.txt lbl)
×
460
                       ++ O.txt ":" ++ O.cut
×
461
                       ++ type_expr ~needs_parentheses:true ty))
×
462
          in
463
          if Syntax.Type.Tuple.always_parenthesize || needs_parentheses then
×
464
            enclose ~l:"(" res ~r:")"
131✔
465
          else res
546✔
466
      | Constr (path, args) ->
179,418✔
467
          let link = Link.from_path (path :> Paths.Path.t) in
468
          format_type_path ~delim:`parens args link
179,418✔
469
      | Polymorphic_variant v -> te_variant v
75,143✔
470
      | Object o -> te_object o
80✔
471
      | Class (path, args) ->
8✔
472
          format_type_path ~delim:`brackets args
473
            (Link.from_path (path :> Paths.Path.t))
8✔
474
      | Poly (polyvars, t) ->
24✔
475
          O.txt ("'" ^ String.concat ~sep:" '" polyvars ^ ". ") ++ type_expr t
24✔
476
      | Package pkg ->
24✔
477
          enclose ~l:"(" ~r:")"
478
            (O.keyword "module" ++ O.txt " "
24✔
479
            ++ Link.from_path (pkg.path :> Paths.Path.t)
24✔
480
            ++
24✔
481
            match pkg.substitutions with
482
            | [] -> O.noop
16✔
483
            | fst :: lst ->
8✔
484
                O.sp
485
                ++ O.box_hv (O.keyword "with" ++ O.txt " " ++ package_subst fst)
8✔
486
                ++ O.list lst ~f:(fun s ->
8✔
487
                       O.cut
8✔
488
                       ++ (O.box_hv
8✔
489
                          @@ O.txt " " ++ O.keyword "and" ++ O.txt " "
8✔
490
                             ++ package_subst s)))
8✔
491

492
    and package_subst
493
        ((frag_typ, te) : Paths.Fragment.Type.t * Odoc_model.Lang.TypeExpr.t) :
494
        text =
495
      let typath = Link.from_fragment (frag_typ :> Paths.Fragment.leaf) in
16✔
496
      O.keyword "type" ++ O.txt " " ++ typath ++ O.txt " =" ++ O.sp
16✔
497
      ++ type_expr te
16✔
498
  end
499

500
  open Type_expression
501

502
  (* Also handles constructor declarations for exceptions and extensible
503
     variants, and exposes a few helpers used in formatting classes and signature
504
     constraints. *)
505
  module Type_declaration : sig
506
    val type_decl :
507
      ?is_substitution:bool ->
508
      Lang.Signature.recursive * Lang.TypeDecl.t ->
509
      Item.t
510

511
    val extension : Lang.Extension.t -> Item.t
512

513
    val record : Lang.TypeDecl.Field.t list -> DocumentedSrc.one list
514

515
    val exn : Lang.Exception.t -> Item.t
516

517
    val format_params :
518
      ?delim:[ `parens | `brackets ] -> Lang.TypeDecl.param list -> text
519

520
    val format_manifest :
521
      ?is_substitution:bool ->
522
      ?compact_variants:bool ->
523
      Lang.TypeDecl.Equation.t ->
524
      text * bool
525

526
    val format_constraints : (Lang.TypeExpr.t * Lang.TypeExpr.t) list -> text
527
  end = struct
528
    let record fields =
529
      let field mutable_ id typ =
85✔
530
        let url = Url.from_identifier ~stop_before:true id in
154✔
531
        let name = Paths.Identifier.name id in
154✔
532
        let attrs = [ "def"; "record"; Url.Anchor.string_of_kind url.kind ] in
154✔
533
        let cell =
534
          (* O.td ~a:[ O.a_class ["def"; kind ] ]
535
           *   [O.a ~a:[O.a_href ("#" ^ anchor); O.a_class ["anchor"]] []
536
           *   ; *)
537
          O.code
538
            ((if mutable_ then O.keyword "mutable" ++ O.txt " " else O.noop)
24✔
539
            ++ O.txt name
154✔
540
            ++ O.txt Syntax.Type.annotation_separator
154✔
541
            ++ type_expr typ
154✔
542
            ++ O.txt Syntax.Type.Record.field_separator)
154✔
543
          (* ] *)
544
        in
545
        (url, attrs, cell)
154✔
546
      in
547
      let rows =
548
        fields
549
        |> List.map (fun fld ->
550
               let open Odoc_model.Lang.TypeDecl.Field in
154✔
551
               let url, attrs, code =
552
                 field fld.mutable_ (fld.id :> Paths.Identifier.t) fld.type_
553
               in
554
               let anchor = Some url in
154✔
555
               let doc = fld.doc.elements in
556
               let rhs = Comment.to_ir doc in
557
               let doc = if not (Comment.has_doc doc) then [] else rhs in
64✔
558
               let markers = Syntax.Comment.markers in
559
               DocumentedSrc.Documented { anchor; attrs; code; doc; markers })
560
      in
561
      let content =
85✔
562
        O.documentedSrc (O.txt "{") @ rows @ O.documentedSrc (O.txt "}")
85✔
563
      in
564
      content
565

566
    let constructor :
567
        Paths.Identifier.t ->
568
        Odoc_model.Lang.TypeDecl.Constructor.argument ->
569
        Odoc_model.Lang.TypeExpr.t option ->
570
        DocumentedSrc.t =
571
     fun id args ret_type ->
572
      let name = Paths.Identifier.name id in
656✔
573
      let kind = Url.(kind id |> Anchor.string_of_kind) in
656✔
574
      let cstr = tag kind (O.txt name) in
656✔
575
      let is_gadt, ret_type =
656✔
576
        match ret_type with
577
        | None -> (false, O.noop)
520✔
578
        | Some te ->
136✔
579
            let constant = match args with Tuple [] -> true | _ -> false in
48✔
580
            let ret_type =
581
              O.txt " "
136✔
582
              ++ (if constant then O.txt ":" else Syntax.Type.GADT.arrow)
48✔
583
              ++ O.txt " " ++ type_expr te
136✔
584
            in
585
            (true, ret_type)
136✔
586
      in
587
      match args with
588
      | Tuple [] -> O.documentedSrc (cstr ++ ret_type)
289✔
589
      | Tuple lst ->
350✔
590
          let params =
591
            O.list lst ~sep:Syntax.Type.Tuple.element_separator
592
              ~f:(type_expr ~needs_parentheses:is_gadt)
593
          in
594
          O.documentedSrc
350✔
595
            (cstr
596
            ++ (if Syntax.Type.Variant.parenthesize_params then
350✔
597
                  O.txt "(" ++ params ++ O.txt ")"
×
598
                else
599
                  (if is_gadt then O.txt Syntax.Type.annotation_separator
88✔
600
                   else O.txt " " ++ O.keyword "of" ++ O.txt " ")
262✔
601
                  ++ params)
350✔
602
            ++ ret_type)
350✔
603
      | Record fields ->
17✔
604
          if is_gadt then
605
            O.documentedSrc (cstr ++ O.txt Syntax.Type.annotation_separator)
×
606
            @ record fields @ O.documentedSrc ret_type
×
607
          else
608
            O.documentedSrc (cstr ++ O.txt " " ++ O.keyword "of" ++ O.txt " ")
17✔
609
            @ record fields
17✔
610

611
    let variant cstrs : DocumentedSrc.t =
612
      let constructor id args res =
235✔
613
        let url = Url.from_identifier ~stop_before:true id in
436✔
614
        let attrs = [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ] in
436✔
615
        let content =
616
          let doc = constructor id args res in
617
          O.documentedSrc (O.txt "| ") @ doc
436✔
618
        in
619
        (url, attrs, content)
620
      in
621
      match cstrs with
622
      | [] -> O.documentedSrc (O.txt "|")
×
623
      | _ :: _ ->
235✔
624
          let rows =
625
            cstrs
626
            |> List.map (fun cstr ->
627
                   let open Odoc_model.Lang.TypeDecl.Constructor in
436✔
628
                   let url, attrs, code =
629
                     constructor
630
                       (cstr.id :> Paths.Identifier.t)
631
                       cstr.args cstr.res
632
                   in
633
                   let anchor = Some url in
436✔
634
                   let doc = cstr.doc.elements in
635
                   let rhs = Comment.to_ir doc in
636
                   let doc = if not (Comment.has_doc doc) then [] else rhs in
73✔
637
                   let markers = Syntax.Comment.markers in
638
                   DocumentedSrc.Nested { anchor; attrs; code; doc; markers })
639
          in
640
          rows
235✔
641

642
    let extension_constructor (t : Odoc_model.Lang.Extension.Constructor.t) =
643
      let id = (t.id :> Paths.Identifier.t) in
154✔
644
      let url = Url.from_identifier ~stop_before:true id in
645
      let anchor = Some url in
154✔
646
      let attrs = [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ] in
154✔
647
      let code = O.documentedSrc (O.txt "| ") @ constructor id t.args t.res in
154✔
648
      let doc = Comment.to_ir t.doc.elements in
649
      let markers = Syntax.Comment.markers in
154✔
650
      DocumentedSrc.Nested { anchor; attrs; code; doc; markers }
651

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

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

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

767
    let format_params :
768
        'row.
769
        ?delim:[ `parens | `brackets ] ->
770
        Odoc_model.Lang.TypeDecl.param list ->
771
        text =
772
     fun ?(delim = `parens) params ->
461✔
773
      let format_param { Odoc_model.Lang.TypeDecl.desc; variance; injectivity }
552✔
774
          =
775
        let desc =
605✔
776
          match desc with
777
          | Odoc_model.Lang.TypeDecl.Any -> [ "_" ]
33✔
778
          | Var s -> [ "'"; s ]
572✔
779
        in
780
        let var_desc =
781
          match variance with
782
          | None -> desc
589✔
783
          | Some Odoc_model.Lang.TypeDecl.Pos -> "+" :: desc
8✔
784
          | Some Odoc_model.Lang.TypeDecl.Neg -> "-" :: desc
8✔
785
          | Some Odoc_model.Lang.TypeDecl.Bivariant -> "+" :: "-" :: desc
×
786
        in
787
        let final = if injectivity then "!" :: var_desc else var_desc in
×
788
        String.concat ~sep:"" final
789
      in
790
      O.txt
791
        (match params with
792
        | [] -> ""
59✔
793
        | [ x ] -> format_param x |> Syntax.Type.handle_format_params
381✔
794
        | lst -> (
112✔
795
            let params = String.concat ~sep:", " (List.map format_param lst) in
112✔
796
            (match delim with `parens -> "(" | `brackets -> "[")
×
797
            ^ params
798
            ^ match delim with `parens -> ")" | `brackets -> "]"))
×
799

800
    let format_constraints constraints =
801
      O.list constraints ~f:(fun (t1, t2) ->
3,084✔
802
          O.sp
104✔
803
          ++ (O.box_hv
104✔
804
             @@ O.keyword "constraint" ++ O.sp
104✔
805
                ++ O.box_hv_no_indent (type_expr t1)
104✔
806
                ++ O.txt " =" ++ O.sp
104✔
807
                ++ O.box_hv_no_indent (type_expr t2)))
104✔
808

809
    let format_manifest :
810
        'inner_row 'outer_row.
811
        ?is_substitution:bool ->
812
        ?compact_variants:bool ->
813
        Odoc_model.Lang.TypeDecl.Equation.t ->
814
        text * bool =
815
     fun ?(is_substitution = false) ?(compact_variants = true) equation ->
104✔
816
      let _ = compact_variants in
3,002✔
817
      (* TODO *)
818
      let private_ = equation.private_ in
819
      match equation.manifest with
820
      | None -> (O.noop, private_)
1,742✔
821
      | Some t ->
1,260✔
822
          let manifest =
823
            O.txt (if is_substitution then " :=" else " =")
16✔
824
            ++ O.sp
1,260✔
825
            ++ (if private_ then
1,260✔
826
                  O.keyword Syntax.Type.private_keyword ++ O.txt " "
8✔
827
                else O.noop)
1,252✔
828
            ++ type_expr t
1,260✔
829
          in
830
          (manifest, false)
1,260✔
831

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

910
  open Type_declaration
911

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

938
  open Value
939

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

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

948
    val comment_items : Comment.elements -> Item.t list
949

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

963
    let comment_items (input0 : Odoc_model.Comment.elements) =
964
      let rec loop input_comment acc =
958✔
965
        match input_comment with
2,483✔
966
        | [] -> List.rev acc
958✔
967
        | element :: input_comment -> (
1,525✔
968
            match element.Location.value with
969
            | `Heading h ->
837✔
970
                let item = Comment.heading h in
971
                loop input_comment (item :: acc)
837✔
972
            | _ ->
688✔
973
                let content, input_comment =
974
                  take_until_heading_or_end (element :: input_comment)
975
                in
976
                let item = Item.Text content in
688✔
977
                loop input_comment (item :: acc))
978
      in
979
      loop input0 []
980

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

1005
  module Class : sig
1006
    val class_ : Lang.Class.t -> Item.t
1007

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

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

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

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

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

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

1104
    let rec class_decl (cd : Odoc_model.Lang.Class.decl) =
1105
      match cd with
182✔
1106
      | ClassType expr -> class_type_expr expr
166✔
1107
      (* TODO: factorize the following with [type_expr] *)
1108
      | Arrow (None, src, dst) ->
16✔
1109
          O.span
16✔
1110
            (type_expr ~needs_parentheses:true src
16✔
1111
            ++ O.txt " " ++ Syntax.Type.arrow)
16✔
1112
          ++ O.txt " " ++ class_decl dst
16✔
1113
      | Arrow (Some (RawOptional _ as lbl), _src, dst) ->
×
1114
          O.span
×
1115
            (O.box_hv
×
1116
            @@ label lbl ++ O.txt ":"
×
1117
               ++ tag "error" (O.txt "???")
×
1118
               ++ O.txt " " ++ Syntax.Type.arrow)
×
1119
          ++ O.sp ++ class_decl dst
×
1120
      | Arrow (Some lbl, src, dst) ->
×
1121
          O.span
×
1122
            (label lbl ++ O.txt ":"
×
1123
            ++ type_expr ~needs_parentheses:true src
×
1124
            ++ O.txt " " ++ Syntax.Type.arrow)
×
1125
          ++ O.txt " " ++ class_decl dst
×
1126

1127
    let class_ (t : Odoc_model.Lang.Class.t) =
1128
      let name = Paths.Identifier.name t.id in
166✔
1129
      let params =
166✔
1130
        match t.params with
1131
        | [] -> O.noop
142✔
1132
        | _ :: _ as params -> format_params ~delim:`brackets params ++ O.txt " "
24✔
1133
      in
1134
      let virtual_ =
1135
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
24✔
1136
      in
1137

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

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

1207
  open Class
1208

1209
  module Module : sig
1210
    val signature : Lang.Signature.t -> Comment.Comment.elements * Item.t list
1211
    (** Returns [header_doc, content]. *)
1212
  end = struct
1213
    let internal_module m =
1214
      let open Lang.Module in
1,924✔
1215
      match m.id.iv with
1216
      | `Module (_, name) when ModuleName.is_hidden name -> true
81✔
1217
      | _ -> false
1,843✔
1218

1219
    let internal_type t =
1220
      let open Lang.TypeDecl in
2,957✔
1221
      match t.id.iv with
1222
      | `Type (_, name) when TypeName.is_hidden name -> true
1✔
1223
      | _ -> false
2,956✔
1224

1225
    let internal_value v =
1226
      let open Lang.Value in
993✔
1227
      match v.id.iv with
1228
      | `Value (_, name) when ValueName.is_hidden name -> true
106✔
1229
      | _ -> false
887✔
1230

1231
    let internal_module_type t =
1232
      let open Lang.ModuleType in
1,342✔
1233
      match t.id.iv with
1234
      | `ModuleType (_, name) when ModuleTypeName.is_hidden name -> true
×
1235
      | _ -> false
1,342✔
1236

1237
    let internal_module_substitution t =
1238
      let open Lang.ModuleSubstitution in
8✔
1239
      match t.id.iv with
1240
      | `Module (_, name) when ModuleName.is_hidden name -> true
×
1241
      | _ -> false
8✔
1242

1243
    let internal_module_type_substitution t =
1244
      let open Lang.ModuleTypeSubstitution in
8✔
1245
      match t.id.iv with
1246
      | `ModuleType (_, name) when ModuleTypeName.is_hidden name -> true
×
1247
      | _ -> false
8✔
1248

1249
    let rec signature (s : Lang.Signature.t) =
1250
      let rec loop l acc_items =
3,530✔
1251
        match l with
12,399✔
1252
        | [] -> List.rev acc_items
3,530✔
1253
        | item :: rest -> (
8,869✔
1254
            let continue (item : Item.t) = loop rest (item :: acc_items) in
7,751✔
1255
            match (item : Lang.Signature.item) with
1256
            | Module (_, m) when internal_module m -> loop rest acc_items
81✔
1257
            | Type (_, t) when internal_type t -> loop rest acc_items
1✔
1258
            | Value v when internal_value v -> loop rest acc_items
106✔
1259
            | ModuleType m when internal_module_type m -> loop rest acc_items
×
1260
            | ModuleSubstitution m when internal_module_substitution m ->
8✔
1261
                loop rest acc_items
×
1262
            | ModuleTypeSubstitution m when internal_module_type_substitution m
8✔
1263
              ->
1264
                loop rest acc_items
×
1265
            | ModuleTypeSubstitution m -> continue @@ module_type_substitution m
8✔
1266
            | Module (_, m) -> continue @@ module_ m
1,843✔
1267
            | ModuleType m -> continue @@ module_type m
1,342✔
1268
            | Class (_, c) -> continue @@ class_ c
166✔
1269
            | ClassType (_, c) -> continue @@ class_type c
67✔
1270
            | Include m -> continue @@ include_ m
266✔
1271
            | ModuleSubstitution m -> continue @@ module_substitution m
8✔
1272
            | TypeSubstitution t ->
16✔
1273
                continue @@ type_decl ~is_substitution:true (Ordinary, t)
16✔
1274
            | Type (r, t) -> continue @@ type_decl (r, t)
2,956✔
1275
            | TypExt e -> continue @@ extension e
126✔
1276
            | Exception e -> continue @@ exn e
66✔
1277
            | Value v -> continue @@ value v
887✔
1278
            | Open o ->
82✔
1279
                let items = Sectioning.comment_items o.doc.elements in
1280
                loop rest (List.rev_append items acc_items)
82✔
1281
            | Comment `Stop ->
57✔
1282
                let rest =
1283
                  List.skip_until rest ~p:(function
1284
                    | Lang.Signature.Comment `Stop -> true
49✔
1285
                    | _ -> false)
65✔
1286
                in
1287
                loop rest acc_items
57✔
1288
            | Comment (`Docs c) ->
791✔
1289
                let items = Sectioning.comment_items c.elements in
1290
                loop rest (List.rev_append items acc_items))
791✔
1291
      in
1292
      ((Lang.extract_signature_doc s).elements, loop s.items [])
3,530✔
1293

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

1335
    and module_substitution (t : Odoc_model.Lang.ModuleSubstitution.t) =
1336
      let name = Paths.Identifier.name t.id in
8✔
1337
      let path = Link.from_path (t.manifest :> Paths.Path.t) in
8✔
1338
      let content =
8✔
1339
        O.documentedSrc
1340
          (O.keyword "module" ++ O.txt " " ++ O.txt name ++ O.txt " :=" ++ O.sp
8✔
1341
         ++ path)
8✔
1342
      in
1343
      let attr = [ "module-substitution" ] in
8✔
1344
      let anchor = path_to_id t.id in
1345
      let doc = Comment.to_ir t.doc.elements in
8✔
1346
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
8✔
1347

1348
    and module_type_substitution (t : Odoc_model.Lang.ModuleTypeSubstitution.t)
1349
        =
1350
      let prefix =
8✔
1351
        O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
8✔
1352
      in
1353
      let source_anchor = None in
8✔
1354
      let modname = Paths.Identifier.name t.id in
1355
      let modname, expansion_doc, mty =
8✔
1356
        module_type_manifest ~subst:true ~source_anchor modname t.id
1357
          t.doc.elements (Some t.manifest) prefix
1358
      in
1359
      let content =
8✔
1360
        O.documentedSrc (prefix ++ modname)
8✔
1361
        @ mty
1362
        @ O.documentedSrc
8✔
1363
            (if Syntax.Mod.close_tag_semicolon then O.txt ";" else O.noop)
×
1364
      in
1365
      let attr = [ "module-type" ] in
1366
      let anchor = path_to_id t.id in
1367
      let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
8✔
1368
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1369

1370
    and simple_expansion :
1371
        Odoc_model.Lang.ModuleType.simple_expansion ->
1372
        Comment.Comment.elements * Item.t list =
1373
     fun t ->
1374
      let rec extract_functor_params
2,914✔
1375
          (f : Odoc_model.Lang.ModuleType.simple_expansion) =
1376
        match f with
3,133✔
1377
        | Signature sg -> (None, sg)
2,914✔
1378
        | Functor (p, expansion) ->
219✔
1379
            let add_to params =
1380
              match p with Unit -> params | Named p -> p :: params
8✔
1381
            in
1382
            let params, sg = extract_functor_params expansion in
1383
            let params = match params with None -> [] | Some p -> p in
36✔
1384
            (Some (add_to params), sg)
219✔
1385
      in
1386
      match extract_functor_params t with
1387
      | None, sg -> signature sg
2,731✔
1388
      | Some params, sg ->
183✔
1389
          let sg_doc, content = signature sg in
1390
          let params =
183✔
1391
            let decl_of_arg arg =
1392
              let content = functor_parameter arg in
211✔
1393
              let attr = [ "parameter" ] in
211✔
1394
              let anchor =
1395
                Some (Url.Anchor.from_identifier (arg.id :> Paths.Identifier.t))
211✔
1396
              in
1397
              let doc = [] in
1398
              [
1399
                Item.Declaration
1400
                  { content; anchor; attr; doc; source_anchor = None };
1401
              ]
1402
            in
1403
            List.concat_map decl_of_arg params
183✔
1404
          in
1405
          let prelude = mk_heading ~label:"parameters" "Parameters" :: params
183✔
1406
          and content = mk_heading ~label:"signature" "Signature" :: content in
183✔
1407
          (sg_doc, prelude @ content)
1408

1409
    and expansion_of_module_type_expr :
1410
        Odoc_model.Lang.ModuleType.expr ->
1411
        (Comment.Comment.elements * Item.t list) option =
1412
     fun t ->
1413
      let rec simple_expansion_of (t : Odoc_model.Lang.ModuleType.expr) =
3,199✔
1414
        match t with
3,418✔
1415
        | Path { p_expansion = None; _ }
379✔
1416
        | TypeOf { t_expansion = None; _ }
8✔
1417
        | With { w_expansion = None; _ } ->
×
1418
            None
1419
        | Path { p_expansion = Some e; _ }
426✔
1420
        | TypeOf { t_expansion = Some e; _ }
56✔
1421
        | With { w_expansion = Some e; _ } ->
218✔
1422
            Some e
1423
        | Signature sg -> Some (Signature sg)
2,112✔
1424
        | Functor (f_parameter, e) -> (
219✔
1425
            match simple_expansion_of e with
1426
            | Some e -> Some (Functor (f_parameter, e))
211✔
1427
            | None -> None)
8✔
1428
      in
1429
      match simple_expansion_of t with
1430
      | None -> None
387✔
1431
      | Some e -> Some (simple_expansion e)
2,812✔
1432

1433
    and module_ : Odoc_model.Lang.Module.t -> Item.t =
1434
     fun t ->
1435
      let modname = Paths.Identifier.name t.id in
1,843✔
1436
      let expansion =
1,843✔
1437
        match t.type_ with
1438
        | Alias (_, Some e) -> Some (simple_expansion e)
102✔
1439
        | Alias (_, None) -> None
186✔
1440
        | ModuleType e -> expansion_of_module_type_expr e
1,555✔
1441
      in
1442
      let source_anchor = source_anchor t.source_loc in
1443
      let modname, status, expansion, expansion_doc =
1,843✔
1444
        match expansion with
1445
        | None -> (O.txt modname, `Default, None, None)
322✔
1446
        | Some (expansion_doc, items) ->
1,521✔
1447
            let status =
1448
              match t.type_ with
1449
              | ModuleType (Signature _) -> `Inline
987✔
1450
              | _ -> `Default
534✔
1451
            in
1452
            let url = Url.Path.from_identifier t.id in
1453
            let link = path url [ inline @@ Text modname ] in
1,521✔
1454
            let page =
1,521✔
1455
              make_expansion_page ~source_anchor url
1456
                [ t.doc.elements; expansion_doc ]
1457
                items
1458
            in
1459
            (link, status, Some page, Some expansion_doc)
1,521✔
1460
      in
1461
      let intro = O.keyword "module" ++ O.txt " " ++ modname in
1,843✔
1462
      let summary = O.ignore intro ++ mdexpr_in_decl t.id t.type_ in
1,843✔
1463
      let modexpr =
1,843✔
1464
        attach_expansion ~status
1465
          (Syntax.Type.annotation_separator, "sig", "end")
1466
          expansion summary
1467
      in
1468
      let content =
1,843✔
1469
        O.documentedSrc intro @ modexpr
1,843✔
1470
        @ O.documentedSrc
1,843✔
1471
            (if Syntax.Mod.close_tag_semicolon then O.txt ";" else O.noop)
×
1472
      in
1473
      let attr = [ "module" ] in
1474
      let anchor = path_to_id t.id in
1475
      let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
1,843✔
1476
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1477

1478
    and simple_expansion_in_decl (base : Paths.Identifier.Module.t) se =
1479
      let rec ty_of_se :
102✔
1480
          Lang.ModuleType.simple_expansion -> Lang.ModuleType.expr = function
1481
        | Signature sg -> Signature sg
102✔
1482
        | Functor (arg, sg) -> Functor (arg, ty_of_se sg)
×
1483
      in
1484
      mty_in_decl (base :> Paths.Identifier.Signature.t) (ty_of_se se)
102✔
1485

1486
    and mdexpr_in_decl (base : Paths.Identifier.Module.t) md =
1487
      let sig_dotdotdot =
1,843✔
1488
        O.txt Syntax.Type.annotation_separator
1,843✔
1489
        ++ O.cut ++ Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
1,843✔
1490
      in
1491
      match md with
1,843✔
1492
      | Alias (_, Some se) -> simple_expansion_in_decl base se
102✔
1493
      | Alias (p, _) when not Paths.Path.(is_hidden (p :> t)) ->
186✔
1494
          O.txt " =" ++ O.sp ++ mdexpr md
186✔
1495
      | Alias _ -> sig_dotdotdot
×
1496
      | ModuleType mt -> mty_in_decl (base :> Paths.Identifier.Signature.t) mt
1,555✔
1497

1498
    and mdexpr : Odoc_model.Lang.Module.decl -> text = function
1499
      | Alias (mod_path, _) -> Link.from_path (mod_path :> Paths.Path.t)
242✔
1500
      | ModuleType mt -> mty mt
×
1501

1502
    and module_type_manifest ~subst ~source_anchor modname id doc manifest
1503
        prefix =
1504
      let expansion =
1,350✔
1505
        match manifest with
1506
        | None -> None
128✔
1507
        | Some e -> expansion_of_module_type_expr e
1,222✔
1508
      in
1509
      let modname, expansion, expansion_doc =
1510
        match expansion with
1511
        | None -> (O.txt modname, None, None)
379✔
1512
        | Some (expansion_doc, items) ->
971✔
1513
            let url = Url.Path.from_identifier id in
1514
            let link = path url [ inline @@ Text modname ] in
971✔
1515
            let page =
971✔
1516
              make_expansion_page ~source_anchor url [ doc; expansion_doc ]
1517
                items
1518
            in
1519
            (link, Some page, Some expansion_doc)
971✔
1520
      in
1521
      let summary =
1522
        match manifest with
1523
        | None -> O.noop
128✔
1524
        | Some expr ->
1,222✔
1525
            O.ignore (prefix ++ modname)
1,222✔
1526
            ++ (if subst then O.txt " :=" ++ O.sp else O.txt " =" ++ O.sp)
8✔
1527
            ++ mty expr
1,222✔
1528
      in
1529
      ( modname,
1530
        expansion_doc,
1531
        attach_expansion (" = ", "sig", "end") expansion summary )
1,350✔
1532

1533
    and module_type (t : Odoc_model.Lang.ModuleType.t) =
1534
      let prefix =
1,342✔
1535
        O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
1,342✔
1536
      in
1537
      let modname = Paths.Identifier.name t.id in
1,342✔
1538
      let source_anchor = source_anchor t.source_loc in
1,342✔
1539
      let modname, expansion_doc, mty =
1,342✔
1540
        module_type_manifest ~subst:false ~source_anchor modname t.id
1541
          t.doc.elements t.expr prefix
1542
      in
1543
      let content =
1,342✔
1544
        O.documentedSrc (prefix ++ modname)
1,342✔
1545
        @ mty
1546
        @ O.documentedSrc
1,342✔
1547
            (if Syntax.Mod.close_tag_semicolon then O.txt ";" else O.noop)
×
1548
      in
1549
      let attr = [ "module-type" ] in
1550
      let anchor = path_to_id t.id in
1551
      let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
1,342✔
1552
      Item.Declaration { attr; anchor; doc; content; source_anchor }
1553

1554
    and umty_hidden : Odoc_model.Lang.ModuleType.U.expr -> bool = function
1555
      | Path p -> Paths.Path.(is_hidden (p :> t))
383✔
1556
      | With (_, expr) -> umty_hidden expr
18✔
1557
      | TypeOf (ModPath m, _) | TypeOf (StructInclude m, _) ->
42✔
1558
          Paths.Path.(is_hidden (m :> t))
1559
      | Signature _ -> false
10✔
1560

1561
    and mty_hidden : Odoc_model.Lang.ModuleType.expr -> bool = function
1562
      | Path { p_path = mty_path; _ } -> Paths.Path.(is_hidden (mty_path :> t))
837✔
1563
      | With { w_expr; _ } -> umty_hidden w_expr
218✔
1564
      | TypeOf { t_desc = ModPath m; _ }
48✔
1565
      | TypeOf { t_desc = StructInclude m; _ } ->
16✔
1566
          Paths.Path.(is_hidden (m :> t))
1567
      | _ -> false
2,278✔
1568

1569
    and mty_with subs expr =
1570
      umty expr ++ O.sp ++ O.keyword "with" ++ O.txt " "
234✔
1571
      ++ O.list
234✔
1572
           ~sep:(O.cut ++ O.txt " " ++ O.keyword "and" ++ O.txt " ")
234✔
1573
           ~f:(fun x -> O.span (substitution x))
274✔
1574
           subs
1575

1576
    and mty_typeof t_desc =
1577
      match t_desc with
154✔
1578
      | Odoc_model.Lang.ModuleType.ModPath m ->
90✔
1579
          O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
90✔
1580
          ++ O.keyword "of" ++ O.txt " "
90✔
1581
          ++ Link.from_path (m :> Paths.Path.t)
90✔
1582
      | StructInclude m ->
64✔
1583
          O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
64✔
1584
          ++ O.keyword "of" ++ O.txt " " ++ O.keyword "struct" ++ O.txt " "
64✔
1585
          ++ O.keyword "include" ++ O.txt " "
64✔
1586
          ++ Link.from_path (m :> Paths.Path.t)
64✔
1587
          ++ O.txt " " ++ O.keyword "end"
64✔
1588

1589
    and is_elidable_with_u : Odoc_model.Lang.ModuleType.U.expr -> bool =
1590
      function
1591
      | Path _ -> false
209✔
1592
      | Signature _ -> true
2✔
1593
      | With (_, expr) -> is_elidable_with_u expr
×
1594
      | TypeOf _ -> false
25✔
1595

1596
    and umty : Odoc_model.Lang.ModuleType.U.expr -> text =
1597
     fun m ->
1598
      match m with
499✔
1599
      | Path p -> Link.from_path (p :> Paths.Path.t)
383✔
1600
      | Signature _ ->
8✔
1601
          Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
8✔
1602
      | With (_, expr) when is_elidable_with_u expr ->
18✔
1603
          Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
2✔
1604
      | With (subs, expr) -> mty_with subs expr
16✔
1605
      | TypeOf (t_desc, _) -> mty_typeof t_desc
90✔
1606

1607
    and mty : Odoc_model.Lang.ModuleType.expr -> text =
1608
     fun m ->
1609
      if mty_hidden m then
3,397✔
1610
        Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
×
1611
      else
1612
        match m with
3,397✔
1613
        | Path { p_path = mty_path; _ } ->
837✔
1614
            Link.from_path (mty_path :> Paths.Path.t)
1615
        | Functor (Unit, expr) ->
×
1616
            (if Syntax.Mod.functor_keyword then O.keyword "functor" else O.noop)
×
1617
            ++ O.span (O.txt " () " ++ Syntax.Type.arrow)
×
1618
            ++ O.sp ++ mty expr
×
1619
        | Functor (Named arg, expr) ->
48✔
1620
            let arg_expr = arg.expr in
1621
            let stop_before = expansion_of_module_type_expr arg_expr = None in
48✔
1622
            let name =
1623
              let open Odoc_model.Lang.FunctorParameter in
1624
              let name = Paths.Identifier.name arg.id in
1625
              let href =
48✔
1626
                Url.from_identifier ~stop_before (arg.id :> Paths.Identifier.t)
1627
              in
1628
              resolved href [ inline @@ Text name ]
48✔
1629
            in
1630
            (if Syntax.Mod.functor_keyword then O.keyword "functor" else O.noop)
×
1631
            ++ (O.box_hv @@ O.span
48✔
1632
               @@ O.txt " (" ++ name
48✔
1633
                  ++ O.txt Syntax.Type.annotation_separator
48✔
1634
                  ++ mty arg_expr ++ O.txt ")" ++ O.txt " " ++ Syntax.Type.arrow
48✔
1635
               )
1636
            ++ O.sp ++ mty expr
48✔
1637
        | With { w_expr; _ } when is_elidable_with_u w_expr ->
218✔
1638
            Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
×
1639
        | With { w_substitutions; w_expr; _ } ->
218✔
1640
            O.box_hv @@ mty_with w_substitutions w_expr
218✔
1641
        | TypeOf { t_desc; _ } -> mty_typeof t_desc
64✔
1642
        | Signature _ ->
2,230✔
1643
            Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
2,230✔
1644

1645
    and mty_in_decl :
1646
        Paths.Identifier.Signature.t -> Odoc_model.Lang.ModuleType.expr -> text
1647
        =
1648
     fun base -> function
1649
      | (Path _ | Signature _ | With _ | TypeOf _) as m ->
40✔
1650
          O.txt Syntax.Type.annotation_separator ++ O.cut ++ mty m
1,868✔
1651
      | Functor _ as m when not Syntax.Mod.functor_contraction ->
171✔
1652
          O.txt Syntax.Type.annotation_separator ++ O.cut ++ mty m
×
1653
      | Functor (arg, expr) ->
171✔
1654
          let text_arg =
1655
            match arg with
1656
            | Unit -> O.txt "()"
8✔
1657
            | Named arg ->
163✔
1658
                let arg_expr = arg.expr in
1659
                let stop_before =
1660
                  expansion_of_module_type_expr arg_expr = None
163✔
1661
                in
1662
                let name =
1663
                  let open Odoc_model.Lang.FunctorParameter in
1664
                  let name = Paths.Identifier.name arg.id in
1665
                  let href =
163✔
1666
                    Url.from_identifier ~stop_before
1667
                      (arg.id :> Paths.Identifier.t)
1668
                  in
1669
                  resolved href [ inline @@ Text name ]
163✔
1670
                in
1671
                O.box_hv
163✔
1672
                @@ O.txt "(" ++ name
163✔
1673
                   ++ O.txt Syntax.Type.annotation_separator
163✔
1674
                   ++ O.cut ++ mty arg.expr ++ O.txt ")"
163✔
1675
          in
1676
          O.sp ++ text_arg ++ mty_in_decl base expr
171✔
1677

1678
    (* TODO : Centralize the list juggling for type parameters *)
1679
    and type_expr_in_subst td typath =
1680
      let typath = Link.from_fragment typath in
146✔
1681
      match td.Lang.TypeDecl.Equation.params with
146✔
1682
      | [] -> typath
122✔
1683
      | l -> Syntax.Type.handle_substitution_params typath (format_params l)
24✔
1684

1685
    and substitution : Odoc_model.Lang.ModuleType.substitution -> text =
1686
      function
1687
      | ModuleEq (frag_mod, md) ->
56✔
1688
          O.box_hv
1689
          @@ O.keyword "module" ++ O.txt " "
56✔
1690
             ++ Link.from_fragment (frag_mod :> Paths.Fragment.leaf)
56✔
1691
             ++ O.txt " =" ++ O.sp ++ mdexpr md
56✔
1692
      | ModuleTypeEq (frag_mty, md) ->
32✔
1693
          O.box_hv
1694
          @@ O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
32✔
1695
             ++ Link.from_fragment (frag_mty :> Paths.Fragment.leaf)
32✔
1696
             ++ O.txt " =" ++ O.sp ++ mty md
32✔
1697
      | TypeEq (frag_typ, td) ->
104✔
1698
          O.box_hv
1699
          @@ O.keyword "type" ++ O.txt " "
104✔
1700
             ++ type_expr_in_subst td (frag_typ :> Paths.Fragment.leaf)
104✔
1701
             ++ fst (format_manifest td)
104✔
1702
             ++ format_constraints
104✔
1703
                  td.Odoc_model.Lang.TypeDecl.Equation.constraints
1704
      | ModuleSubst (frag_mod, mod_path) ->
24✔
1705
          O.box_hv
1706
          @@ O.keyword "module" ++ O.txt " "
24✔
1707
             ++ Link.from_fragment (frag_mod :> Paths.Fragment.leaf)
24✔
1708
             ++ O.txt " :=" ++ O.sp
24✔
1709
             ++ Link.from_path (mod_path :> Paths.Path.t)
24✔
1710
      | ModuleTypeSubst (frag_mty, md) ->
16✔
1711
          O.box_hv
1712
          @@ O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
16✔
1713
             ++ Link.from_fragment (frag_mty :> Paths.Fragment.leaf)
16✔
1714
             ++ O.txt " :=" ++ O.sp ++ mty md
16✔
1715
      | TypeSubst (frag_typ, td) -> (
42✔
1716
          O.box_hv
1717
          @@ O.keyword "type" ++ O.txt " "
42✔
1718
             ++ type_expr_in_subst td (frag_typ :> Paths.Fragment.leaf)
42✔
1719
             ++ O.txt " :=" ++ O.sp
42✔
1720
             ++
42✔
1721
             match td.Lang.TypeDecl.Equation.manifest with
1722
             | None -> assert false (* cf loader/cmti *)
1723
             | Some te -> type_expr te)
42✔
1724

1725
    and include_ (t : Odoc_model.Lang.Include.t) =
1726
      let decl_hidden =
266✔
1727
        match t.decl with
1728
        | Alias p -> Paths.Path.(is_hidden (p :> t))
×
1729
        | ModuleType mty -> umty_hidden mty
266✔
1730
      in
1731
      let status = if decl_hidden then `Inline else t.status in
1✔
1732

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

1761
  open Module
1762

1763
  module Page : sig
1764
    val compilation_unit : Lang.Compilation_unit.t -> Document.t
1765

1766
    val page : Lang.Page.t -> Document.t
1767

1768
    val implementation :
1769
      Lang.Implementation.t ->
1770
      Syntax_highlighter.infos ->
1771
      string ->
1772
      Document.t list
1773
  end = struct
1774
    let pack : Lang.Compilation_unit.Packed.t -> Item.t list =
1775
     fun t ->
1776
      let f x =
×
1777
        let id = x.Lang.Compilation_unit.Packed.id in
×
1778
        let modname = Paths.Identifier.name id in
1779
        let md_def =
×
1780
          O.keyword "module" ++ O.txt " " ++ O.txt modname ++ O.txt " = "
×
1781
          ++ Link.from_path (x.path :> Paths.Path.t)
×
1782
        in
1783
        let content = O.documentedSrc md_def in
×
1784
        let anchor =
×
1785
          Some (Url.Anchor.from_identifier (id :> Paths.Identifier.t))
×
1786
        in
1787
        let attr = [ "modules" ] in
1788
        let doc = [] in
1789
        let decl = { Item.anchor; content; attr; doc; source_anchor = None } in
1790
        Item.Declaration decl
1791
      in
1792
      List.map f t
1793

1794
    let compilation_unit (t : Odoc_model.Lang.Compilation_unit.t) =
1795
      let url = Url.Path.from_identifier t.id in
350✔
1796
      let unit_doc, items =
350✔
1797
        match t.content with
1798
        | Module sign -> signature sign
350✔
1799
        | Pack packed -> ([], pack packed)
×
1800
      in
1801
      let source_anchor = source_anchor t.source_loc in
1802
      let page = make_expansion_page ~source_anchor url [ unit_doc ] items in
350✔
1803
      Document.Page page
350✔
1804

1805
    let page (t : Odoc_model.Lang.Page.t) =
1806
      (*let name =
1807
          match t.name.iv with `Page (_, name) | `LeafPage (_, name) -> name
1808
        in*)
1809
      (*let title = Odoc_model.Names.PageName.to_string name in*)
1810
      let url = Url.Path.from_identifier t.name in
69✔
1811
      let preamble, items = Sectioning.docs t.content.elements in
69✔
1812
      let source_anchor = None in
69✔
1813
      Document.Page { Page.preamble; items; url; source_anchor }
1814

1815
    let implementation (v : Odoc_model.Lang.Implementation.t) syntax_info
1816
        source_code =
1817
      match v.id with
28✔
1818
      | None -> []
×
1819
      | Some id ->
28✔
1820
          [
1821
            Document.Source_page
1822
              (Source_page.source id syntax_info v.source_info source_code);
28✔
1823
          ]
1824
  end
1825

1826
  include Page
1827

1828
  let type_expr = type_expr
1829

1830
  let record = record
1831
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