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

ocaml / odoc / 2729

13 Jan 2025 04:56PM UTC coverage: 73.458% (-0.02%) from 73.477%
2729

push

github

jonludlam
Better handling of error in fix for #1001

8 of 16 new or added lines in 1 file covered. (50.0%)

272 existing lines in 4 files now uncovered.

10240 of 13940 relevant lines covered (73.46%)

9981.63 hits per line

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

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

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

24
let tag tag t = O.span ~attr:tag t
249,565✔
25

26
let label t =
27
  match t with
41,949✔
28
  | Odoc_model.Lang.TypeExpr.Label s -> tag "label" (O.txt s)
37,432✔
29
  | Optional s | RawOptional s -> tag "optlabel" (O.txt "?" ++ O.txt s)
1✔
30

31
let type_var tv = tag "type-var" (O.txt tv)
207,055✔
32

33
let enclose ~l ~r x = O.span (O.txt l ++ x ++ O.txt r)
76,326✔
34

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

39
let path p content = resolved (Url.from_path p) content
2,285✔
40

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

45
let path_to_id path =
46
  let url = Url.Anchor.from_identifier (path :> Paths.Identifier.t) in
5,805✔
47
  Some url
5,805✔
48

49
let source_anchor source_loc =
50
  match source_loc with
6,091✔
51
  | Some id ->
95✔
52
      Some
53
        (Url.Anchor.from_identifier
95✔
54
           (id : Paths.Identifier.SourceLocation.t :> Paths.Identifier.t))
55
  | _ -> None
5,996✔
56

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

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

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

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

91
include Generator_signatures
92

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

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

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

148
    let dot prefix suffix = prefix ^ "." ^ suffix
37✔
149

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

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

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

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

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

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

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

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

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

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

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

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

385
    and format_type_path ~delim (params : Odoc_model.Lang.TypeExpr.t list)
386
        (path : text) : text =
387
      O.box_hv
226,575✔
388
      @@
389
      match params with
390
      | [] -> path
121,746✔
391
      | [ param ] ->
58,933✔
392
          let param = type_expr ~needs_parentheses:true param in
393
          let args =
58,933✔
394
            if Syntax.Type.parenthesize_constructor then
UNCOV
395
              O.txt "(" ++ param ++ O.txt ")"
×
396
            else param
58,933✔
397
          in
398
          Syntax.Type.handle_constructor_params path args
58,933✔
399
      | params ->
45,896✔
400
          let params = O.list params ~sep:(O.txt "," ++ O.sp) ~f:type_expr in
45,896✔
401
          let params =
45,896✔
402
            match delim with
403
            | `parens -> enclose ~l:"(" params ~r:")"
45,896✔
UNCOV
404
            | `brackets -> enclose ~l:"[" params ~r:"]"
×
405
          in
406
          Syntax.Type.handle_constructor_params path (O.box_hv params)
45,896✔
407

408
    and type_expr ?(needs_parentheses = false) (t : Odoc_model.Lang.TypeExpr.t)
371,556✔
409
        =
410
      match t with
622,392✔
411
      | Var s -> type_var (Syntax.Type.var_prefix ^ s)
197,893✔
412
      | Any -> type_var Syntax.Type.any
9,162✔
413
      | Alias (te, alias) ->
60✔
414
          type_expr ~needs_parentheses:true te
60✔
415
          ++ O.txt " " ++ O.keyword "as" ++ O.txt " '" ++ O.txt alias
60✔
416
      | Arrow (None, src, dst) ->
136,680✔
417
          let res =
418
            O.span
136,680✔
419
              ((O.box_hv @@ type_expr ~needs_parentheses:true src)
136,680✔
420
              ++ O.txt " " ++ Syntax.Type.arrow)
136,680✔
421
            ++ O.sp ++ type_expr dst
136,680✔
422
            (* ++ O.end_hv *)
423
          in
424
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
23,986✔
425
      | Arrow (Some (RawOptional _ as lbl), _src, dst) ->
1✔
426
          let res =
427
            O.span
1✔
428
              (O.box_hv
1✔
429
              @@ label lbl ++ O.txt ":"
1✔
430
                 ++ tag "error" (O.txt "???")
1✔
431
                 ++ O.txt " " ++ Syntax.Type.arrow)
1✔
432
            ++ O.sp ++ type_expr dst
1✔
433
          in
NEW
434
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
×
435
      | Arrow (Some lbl, src, dst) ->
41,948✔
436
          let res =
437
            O.span
41,948✔
438
              ((O.box_hv
41,948✔
439
               @@ label lbl ++ O.txt ":" ++ O.cut
41,948✔
440
                  ++ (O.box_hv @@ type_expr ~needs_parentheses:true src))
41,948✔
441
              ++ O.txt " " ++ Syntax.Type.arrow)
41,948✔
442
            ++ O.sp ++ type_expr dst
41,948✔
443
          in
444
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
2,577✔
445
      | Tuple lst ->
6,216✔
446
          let res =
447
            O.box_hv_no_indent
448
              (O.list lst ~sep:Syntax.Type.Tuple.element_separator
6,216✔
449
                 ~f:(type_expr ~needs_parentheses:true))
450
          in
UNCOV
451
          if Syntax.Type.Tuple.always_parenthesize || needs_parentheses then
×
452
            enclose ~l:"(" res ~r:")"
2,976✔
453
          else res
3,240✔
454
      | Constr (path, args) ->
226,525✔
455
          let link = Link.from_path (path :> Paths.Path.t) in
456
          format_type_path ~delim:`parens args link
226,525✔
457
      | Polymorphic_variant v -> te_variant v
2,401✔
458
      | Object o -> te_object o
60✔
459
      | Class (path, args) ->
6✔
460
          format_type_path ~delim:`brackets args
461
            (Link.from_path (path :> Paths.Path.t))
6✔
462
      | Poly (polyvars, t) ->
549✔
463
          O.txt ("'" ^ String.concat " '" polyvars ^ ". ") ++ type_expr t
549✔
464
      | Package pkg ->
891✔
465
          enclose ~l:"(" ~r:")"
466
            (O.keyword "module" ++ O.txt " "
891✔
467
            ++ Link.from_path (pkg.path :> Paths.Path.t)
891✔
468
            ++
891✔
469
            match pkg.substitutions with
470
            | [] -> O.noop
120✔
471
            | fst :: lst ->
771✔
472
                O.sp
473
                ++ O.box_hv (O.keyword "with" ++ O.txt " " ++ package_subst fst)
771✔
474
                ++ O.list lst ~f:(fun s ->
771✔
475
                       O.cut
51✔
476
                       ++ (O.box_hv
51✔
477
                          @@ O.txt " " ++ O.keyword "and" ++ O.txt " "
51✔
478
                             ++ package_subst s)))
51✔
479

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

488
  open Type_expression
489

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

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

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

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

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

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

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

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

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

630
    let extension_constructor (t : Odoc_model.Lang.Extension.Constructor.t) =
631
      let id = (t.id :> Paths.Identifier.t) in
118✔
632
      let url = Url.from_identifier ~stop_before:true id in
633
      let anchor = Some url in
118✔
634
      let attrs = [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ] in
118✔
635
      let code = O.documentedSrc (O.txt "| ") @ constructor id t.args t.res in
118✔
636
      let doc = Comment.to_ir t.doc.elements in
637
      let markers = Syntax.Comment.markers in
118✔
638
      DocumentedSrc.Nested { anchor; attrs; code; doc; markers }
639

640
    let extension (t : Odoc_model.Lang.Extension.t) =
641
      let prefix =
96✔
642
        O.keyword "type" ++ O.txt " "
96✔
643
        ++ Link.from_path (t.type_path :> Paths.Path.t)
96✔
644
        ++ O.txt " +=" ++ O.sp
96✔
645
        ++
646
        if t.private_ then O.keyword Syntax.Type.private_keyword ++ O.sp
6✔
647
        else O.noop
90✔
648
      in
649
      let content =
96✔
650
        O.documentedSrc prefix
96✔
651
        @ List.map extension_constructor t.constructors
96✔
652
        @ O.documentedSrc
96✔
UNCOV
653
            (if Syntax.Type.type_def_semicolon then O.txt ";" else O.noop)
×
654
      in
655
      let attr = [ "type"; "extension" ] in
656
      let anchor = Some (Url.Anchor.extension_decl t) in
96✔
657
      let doc = Comment.to_ir t.doc.elements in
658
      let source_anchor =
96✔
659
        (* Take the anchor from the first constructor only for consistency with
660
           regular variants. *)
661
        match t.constructors with
662
        | hd :: _ -> source_anchor hd.source_loc
96✔
UNCOV
663
        | [] -> None
×
664
      in
665
      Item.Declaration { attr; anchor; doc; content; source_anchor }
666

667
    let exn (t : Odoc_model.Lang.Exception.t) =
668
      let cstr = constructor (t.id :> Paths.Identifier.t) t.args t.res in
50✔
669
      let content =
50✔
670
        O.documentedSrc (O.keyword "exception" ++ O.txt " ")
50✔
671
        @ cstr
672
        @ O.documentedSrc
50✔
UNCOV
673
            (if Syntax.Type.Exception.semicolon then O.txt ";" else O.noop)
×
674
      in
675
      let attr = [ "exception" ] in
676
      let anchor = path_to_id t.id in
677
      let doc = Comment.to_ir t.doc.elements in
50✔
678
      let source_anchor = source_anchor t.source_loc in
50✔
679
      Item.Declaration { attr; anchor; doc; content; source_anchor }
50✔
680

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

755
    let format_params :
756
          'row.
757
          ?delim:[ `parens | `brackets ] ->
758
          Odoc_model.Lang.TypeDecl.param list ->
759
          text =
760
     fun ?(delim = `parens) params ->
351✔
761
      let format_param { Odoc_model.Lang.TypeDecl.desc; variance; injectivity }
420✔
762
          =
763
        let desc =
459✔
764
          match desc with
765
          | Odoc_model.Lang.TypeDecl.Any -> [ "_" ]
31✔
766
          | Var s -> [ "'"; s ]
428✔
767
        in
768
        let var_desc =
769
          match variance with
770
          | None -> desc
447✔
771
          | Some Odoc_model.Lang.TypeDecl.Pos -> "+" :: desc
6✔
772
          | Some Odoc_model.Lang.TypeDecl.Neg -> "-" :: desc
6✔
773
        in
UNCOV
774
        let final = if injectivity then "!" :: var_desc else var_desc in
×
775
        String.concat "" final
776
      in
777
      O.txt
778
        (match params with
779
        | [] -> ""
45✔
780
        | [ x ] -> format_param x |> Syntax.Type.handle_format_params
291✔
781
        | lst -> (
84✔
782
            let params = String.concat ", " (List.map format_param lst) in
84✔
783
            (match delim with `parens -> "(" | `brackets -> "[")
×
784
            ^ params
UNCOV
785
            ^ match delim with `parens -> ")" | `brackets -> "]"))
×
786

787
    let format_constraints constraints =
788
      O.list constraints ~f:(fun (t1, t2) ->
2,406✔
789
          O.sp
78✔
790
          ++ (O.box_hv
78✔
791
             @@ O.keyword "constraint" ++ O.sp
78✔
792
                ++ O.box_hv_no_indent (type_expr t1)
78✔
793
                ++ O.txt " =" ++ O.sp
78✔
794
                ++ O.box_hv_no_indent (type_expr t2)))
78✔
795

796
    let format_manifest :
797
          'inner_row 'outer_row.
798
          ?is_substitution:bool ->
799
          ?compact_variants:bool ->
800
          Odoc_model.Lang.TypeDecl.Equation.t ->
801
          text * bool =
802
     fun ?(is_substitution = false) ?(compact_variants = true) equation ->
78✔
803
      let _ = compact_variants in
2,332✔
804
      (* TODO *)
805
      let private_ = equation.private_ in
806
      match equation.manifest with
807
      | None -> (O.noop, private_)
1,360✔
808
      | Some t ->
972✔
809
          let manifest =
810
            O.txt (if is_substitution then " :=" else " =")
18✔
811
            ++ O.sp
972✔
812
            ++ (if private_ then
972✔
813
                  O.keyword Syntax.Type.private_keyword ++ O.txt " "
6✔
814
                else O.noop)
966✔
815
            ++ type_expr t
972✔
816
          in
817
          (manifest, false)
972✔
818

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

897
  open Type_declaration
898

899
  module Value : sig
900
    val value : Lang.Value.t -> Item.t
901
  end = struct
902
    let value (t : Odoc_model.Lang.Value.t) =
903
      let extra_attr, semicolon =
692✔
904
        match t.value with
905
        | Abstract -> ([], Syntax.Value.semicolon)
674✔
906
        | External _ -> ([ "external" ], Syntax.Type.External.semicolon)
18✔
907
      in
908
      let name = Paths.Identifier.name t.id in
909
      let content =
692✔
910
        O.documentedSrc
911
          (O.box_hv
692✔
912
          @@ O.keyword Syntax.Value.variable_keyword
692✔
913
             ++ O.txt " " ++ O.txt name
692✔
914
             ++ O.txt Syntax.Type.annotation_separator
692✔
915
             ++ O.cut ++ type_expr t.type_
692✔
UNCOV
916
             ++ if semicolon then O.txt ";" else O.noop)
×
917
      in
918
      let attr = [ "value" ] @ extra_attr in
692✔
919
      let anchor = path_to_id t.id in
920
      let doc = Comment.to_ir t.doc.elements in
692✔
921
      let source_anchor = source_anchor t.source_loc in
692✔
922
      Item.Declaration { attr; anchor; doc; content; source_anchor }
692✔
923
  end
924

925
  open Value
926

927
  (* This chunk of code is responsible for sectioning list of items
928
     according to headings by extracting headings as Items.
929

930
     TODO: This sectioning would be better done as a pass on the model directly.
931
  *)
932
  module Sectioning : sig
933
    open Odoc_model
934

935
    val comment_items : Comment.elements -> Item.t list
936

937
    val docs : Comment.elements -> Item.t list * Item.t list
938
  end = struct
939
    let take_until_heading_or_end (docs : Odoc_model.Comment.elements) =
940
      let content, _, rest =
525✔
941
        Doctree.Take.until docs ~classify:(fun b ->
942
            match b.Location.value with
1,102✔
943
            | `Heading _ -> Stop_and_keep
146✔
944
            | #Odoc_model.Comment.attached_block_element as doc ->
956✔
945
                let content = Comment.attached_block_element doc in
946
                Accum content)
956✔
947
      in
948
      (content, rest)
525✔
949

950
    let comment_items (input0 : Odoc_model.Comment.elements) =
951
      let rec loop input_comment acc =
741✔
952
        match input_comment with
1,906✔
953
        | [] -> List.rev acc
741✔
954
        | element :: input_comment -> (
1,165✔
955
            match element.Location.value with
956
            | `Heading h ->
640✔
957
                let item = Comment.heading h in
958
                loop input_comment (item :: acc)
640✔
959
            | _ ->
525✔
960
                let content, input_comment =
961
                  take_until_heading_or_end (element :: input_comment)
962
                in
963
                let item = Item.Text content in
525✔
964
                loop input_comment (item :: acc))
965
      in
966
      loop input0 []
967

968
    (* For doc pages, we want the header to contain everything until
969
       the first heading, then everything before the next heading which
970
       is either lower, or a section.
971
    *)
972
    let docs input_comment =
973
      let items = comment_items input_comment in
65✔
974
      let until_first_heading, o, items =
65✔
975
        Doctree.Take.until items ~classify:(function
976
          | Item.Heading h as i -> Stop_and_accum ([ i ], Some h.level)
65✔
UNCOV
977
          | i -> Accum [ i ])
×
978
      in
979
      match o with
65✔
980
      | None -> (until_first_heading, items)
×
981
      | Some level ->
65✔
UNCOV
982
          let max_level = if level = 1 then 2 else level in
×
983
          let before_second_heading, _, items =
984
            Doctree.Take.until items ~classify:(function
985
              | Item.Heading h when h.level >= max_level -> Stop_and_keep
10✔
986
              | i -> Accum [ i ])
35✔
987
          in
988
          let header = until_first_heading @ before_second_heading in
65✔
989
          (header, items)
990
  end
991

992
  module Class : sig
993
    val class_ : Lang.Class.t -> Item.t
994

995
    val class_type : Lang.ClassType.t -> Item.t
996
  end = struct
997
    let class_type_expr (cte : Odoc_model.Lang.ClassType.expr) =
998
      match cte with
189✔
999
      | Constr (path, args) ->
44✔
1000
          let link = Link.from_path (path :> Paths.Path.t) in
1001
          format_type_path ~delim:`brackets args link
44✔
1002
      | Signature _ ->
145✔
1003
          Syntax.Class.open_tag ++ O.txt " ... " ++ Syntax.Class.close_tag
145✔
1004

1005
    let method_ (t : Odoc_model.Lang.Method.t) =
1006
      let name = Paths.Identifier.name t.id in
68✔
1007
      let virtual_ =
68✔
1008
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
6✔
1009
      in
1010
      let private_ =
1011
        if t.private_ then O.keyword "private" ++ O.txt " " else O.noop
6✔
1012
      in
1013
      let content =
1014
        O.documentedSrc
1015
          (O.keyword "method" ++ O.txt " " ++ private_ ++ virtual_ ++ O.txt name
68✔
1016
          ++ O.txt Syntax.Type.annotation_separator
68✔
1017
          ++ type_expr t.type_)
68✔
1018
      in
1019
      let attr = [ "method" ] in
68✔
1020
      let anchor = path_to_id t.id in
1021
      let doc = Comment.to_ir t.doc.elements in
68✔
1022
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
68✔
1023

1024
    let instance_variable (t : Odoc_model.Lang.InstanceVariable.t) =
1025
      let name = Paths.Identifier.name t.id in
13✔
1026
      let virtual_ =
13✔
1027
        if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
6✔
1028
      in
1029
      let mutable_ =
1030
        if t.mutable_ then O.keyword "mutable" ++ O.txt " " else O.noop
6✔
1031
      in
1032
      let content =
1033
        O.documentedSrc
1034
          (O.keyword "val" ++ O.txt " " ++ mutable_ ++ virtual_ ++ O.txt name
13✔
1035
          ++ O.txt Syntax.Type.annotation_separator
13✔
1036
          ++ type_expr t.type_)
13✔
1037
      in
1038
      let attr = [ "value"; "instance-variable" ] in
13✔
1039
      let anchor = path_to_id t.id in
1040
      let doc = Comment.to_ir t.doc.elements in
13✔
1041
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
13✔
1042

1043
    let inherit_ (ih : Lang.ClassSignature.Inherit.t) =
1044
      let cte =
12✔
1045
        match ih.expr with
1046
        | Signature _ -> assert false (* Bold. *)
1047
        | cty -> cty
12✔
1048
      in
1049
      let content =
1050
        O.documentedSrc (O.keyword "inherit" ++ O.txt " " ++ class_type_expr cte)
12✔
1051
      in
1052
      let attr = [ "inherit" ] in
12✔
1053
      let anchor = None in
1054
      let doc = Comment.to_ir ih.doc.elements in
1055
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
12✔
1056

1057
    let constraint_ (cst : Lang.ClassSignature.Constraint.t) =
1058
      let content =
6✔
1059
        O.documentedSrc (format_constraints [ (cst.left, cst.right) ])
6✔
1060
      in
1061
      let attr = [] in
6✔
1062
      let anchor = None in
1063
      let doc = Comment.to_ir cst.doc.elements in
1064
      Item.Declaration { attr; anchor; doc; content; source_anchor = None }
6✔
1065

1066
    let class_signature (c : Lang.ClassSignature.t) =
1067
      let rec loop l acc_items =
177✔
1068
        match l with
294✔
1069
        | [] -> List.rev acc_items
177✔
1070
        | item :: rest -> (
117✔
1071
            let continue item = loop rest (item :: acc_items) in
99✔
1072
            match (item : Lang.ClassSignature.item) with
1073
            | Inherit cty -> continue @@ inherit_ cty
12✔
1074
            | Method m -> continue @@ method_ m
68✔
1075
            | InstanceVariable v -> continue @@ instance_variable v
13✔
1076
            | Constraint cst -> continue @@ constraint_ cst
6✔
1077
            | Comment `Stop ->
6✔
1078
                let rest =
1079
                  Utils.skip_until rest ~p:(function
1080
                    | Lang.ClassSignature.Comment `Stop -> true
6✔
1081
                    | _ -> false)
6✔
1082
                in
1083
                loop rest acc_items
6✔
1084
            | Comment (`Docs c) ->
12✔
1085
                let items = Sectioning.comment_items c.elements in
1086
                loop rest (List.rev_append items acc_items))
12✔
1087
      in
1088
      (* FIXME: use [t.self] *)
1089
      (c.doc.elements, loop c.items [])
177✔
1090

1091
    let rec class_decl (cd : Odoc_model.Lang.Class.decl) =
1092
      match cd with
138✔
1093
      | ClassType expr -> class_type_expr expr
126✔
1094
      (* TODO: factorize the following with [type_expr] *)
1095
      | Arrow (None, src, dst) ->
12✔
1096
          O.span
12✔
1097
            (type_expr ~needs_parentheses:true src
12✔
1098
            ++ O.txt " " ++ Syntax.Type.arrow)
12✔
1099
          ++ O.txt " " ++ class_decl dst
12✔
NEW
1100
      | Arrow (Some (RawOptional _ as lbl), _src, dst) ->
×
NEW
1101
          O.span
×
NEW
1102
            (O.box_hv
×
NEW
1103
            @@ label lbl ++ O.txt ":"
×
NEW
1104
               ++ tag "error" (O.txt "???")
×
NEW
1105
               ++ O.txt " " ++ Syntax.Type.arrow)
×
NEW
1106
          ++ O.sp ++ class_decl dst
×
1107
      | Arrow (Some lbl, src, dst) ->
×
1108
          O.span
×
1109
            (label lbl ++ O.txt ":"
×
1110
            ++ type_expr ~needs_parentheses:true src
×
UNCOV
1111
            ++ O.txt " " ++ Syntax.Type.arrow)
×
UNCOV
1112
          ++ O.txt " " ++ class_decl dst
×
1113

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

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

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

1194
  open Class
1195

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

1747
  open Module
1748

1749
  module Page : sig
1750
    val compilation_unit : Lang.Compilation_unit.t -> Document.t
1751

1752
    val page : Lang.Page.t -> Document.t
1753

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

1780
    let compilation_unit (t : Odoc_model.Lang.Compilation_unit.t) =
1781
      let url = Url.Path.from_identifier t.id in
289✔
1782
      let unit_doc, items =
289✔
1783
        match t.content with
1784
        | Module sign -> signature sign
289✔
UNCOV
1785
        | Pack packed -> ([], pack packed)
×
1786
      in
1787
      let source_anchor = source_anchor t.source_loc in
1788
      let page = make_expansion_page ~source_anchor url [ unit_doc ] items in
289✔
1789
      Document.Page page
289✔
1790

1791
    let page (t : Odoc_model.Lang.Page.t) =
1792
      (*let name =
1793
          match t.name.iv with `Page (_, name) | `LeafPage (_, name) -> name
1794
        in*)
1795
      (*let title = Odoc_model.Names.PageName.to_string name in*)
1796
      let url = Url.Path.from_identifier t.name in
65✔
1797
      let preamble, items = Sectioning.docs t.content.elements in
65✔
1798
      let source_anchor = None in
65✔
1799
      Document.Page { Page.preamble; items; url; source_anchor }
1800

1801
    let implementation (v : Odoc_model.Lang.Implementation.t) syntax_info
1802
        source_code =
1803
      match v.id with
27✔
UNCOV
1804
      | None -> []
×
1805
      | Some id ->
27✔
1806
          [
1807
            Document.Source_page
1808
              (Source_page.source id syntax_info v.source_info source_code);
27✔
1809
          ]
1810
  end
1811

1812
  include Page
1813

1814
  let type_expr = type_expr
1815

1816
  let record = record
1817
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