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

ocaml / odoc / 3015

15 Jul 2025 04:41PM UTC coverage: 72.941% (-0.1%) from 73.057%
3015

push

github

jonludlam
Promote tests

10386 of 14239 relevant lines covered (72.94%)

7134.98 hits per line

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

85.95
/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
      match id with
290✔
192
      | Some id ->
290✔
193
          let href = Url.from_identifier ~stop_before:false id in
194
          resolved href [ inline @@ Text txt ]
290✔
195
      | None -> unresolved [ inline @@ Text txt ]
×
196

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

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

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

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

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

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

304
  module Type_expression : sig
305
    val type_expr : ?needs_parentheses:bool -> Lang.TypeExpr.t -> text
306

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

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

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

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

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

503
  open Type_expression
504

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

514
    val extension : Lang.Extension.t -> Item.t
515

516
    val record : Lang.TypeDecl.Field.t list -> DocumentedSrc.one list
517

518
    val exn : Lang.Exception.t -> Item.t
519

520
    val format_params :
521
      ?delim:[ `parens | `brackets ] -> Lang.TypeDecl.param list -> text
522

523
    val format_manifest :
524
      ?is_substitution:bool ->
525
      ?compact_variants:bool ->
526
      Lang.TypeDecl.Equation.t ->
527
      text * bool
528

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

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

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

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

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

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

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

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

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

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

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

913
  open Type_declaration
914

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

941
  open Value
942

943
  (* This chunk of code is responsible for sectioning list of items
944
     according to headings by extracting headings as Items.
945

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

951
    val comment_items : Comment.elements -> Item.t list
952

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

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

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

1008
  module Class : sig
1009
    val class_ : Lang.Class.t -> Item.t
1010

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

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

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

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

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

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

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

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

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

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

1210
  open Class
1211

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

1764
  open Module
1765

1766
  module Page : sig
1767
    val compilation_unit : Lang.Compilation_unit.t -> Document.t
1768

1769
    val page : Lang.Page.t -> Document.t
1770

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

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

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

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

1829
  include Page
1830

1831
  let type_expr = type_expr
1832

1833
  let record = record
1834
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