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

ocaml / odoc / 2724

13 Jan 2025 03:52PM UTC coverage: 73.466% (-0.01%) from 73.477%
2724

Pull #1272

github

web-flow
Merge 4efb40676 into e3b301584
Pull Request #1272: Fix #1001

28 of 42 new or added lines in 4 files covered. (66.67%)

63 existing lines in 1 file now uncovered.

10239 of 13937 relevant lines covered (73.47%)

9983.77 hits per line

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

87.61
/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)
×
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✔
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
120
          link ++ O.txt ("." ^ ModuleTypeName.to_string suffix)
×
121
      | `DotV (prefix, suffix) ->
×
122
          let link = from_path (prefix :> Path.t) in
123
          link ++ O.txt ("." ^ ValueName.to_string suffix)
×
124
      | `Apply (p1, p2) ->
×
125
          let link1 = from_path (p1 :> Path.t) in
126
          let link2 = from_path (p2 :> Path.t) in
×
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
×
155
      | `Dot (prefix, suffix) ->
×
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✔
169
        | `Class (`Root _, s) -> TypeName.to_string s
×
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) ->
×
182
            dot (render_resolved_fragment (rr :> t)) (TypeName.to_string s)
×
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✔
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✔
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)` *)
314
          if Syntax.Type.Variant.parenthesize_params then fun x ->
×
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✔
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
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✔
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
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✔
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 lbl, src, dst) ->
41,949✔
426
          let res =
427
            match lbl with
428
            | RawOptional _ ->
1✔
429
              O.span
1✔
430
              ((O.box_hv
1✔
431
               @@ label lbl ++ O.txt ":" ++ tag "error" (O.txt "???")
1✔
432
                ++ O.txt " " ++ Syntax.Type.arrow))
1✔
433
                ++ O.sp ++ type_expr dst
1✔
434
            | _ -> O.span
41,948✔
435
              ((O.box_hv
41,948✔
436
               @@ label lbl ++ O.txt ":" ++ O.cut
41,948✔
437
                  ++ (O.box_hv @@ type_expr ~needs_parentheses:true src))
41,948✔
438
              ++ O.txt " " ++ Syntax.Type.arrow)
41,948✔
439
            ++ O.sp ++ type_expr dst
41,948✔
440
          in
441
          if not needs_parentheses then res else enclose ~l:"(" res ~r:")"
2,577✔
442
      | Tuple lst ->
6,216✔
443
          let res =
444
            O.box_hv_no_indent
445
              (O.list lst ~sep:Syntax.Type.Tuple.element_separator
6,216✔
446
                 ~f:(type_expr ~needs_parentheses:true))
447
          in
UNCOV
448
          if Syntax.Type.Tuple.always_parenthesize || needs_parentheses then
×
449
            enclose ~l:"(" res ~r:")"
2,976✔
450
          else res
3,240✔
451
      | Constr (path, args) ->
226,525✔
452
          let link = Link.from_path (path :> Paths.Path.t) in
453
          format_type_path ~delim:`parens args link
226,525✔
454
      | Polymorphic_variant v -> te_variant v
2,401✔
455
      | Object o -> te_object o
60✔
456
      | Class (path, args) ->
6✔
457
          format_type_path ~delim:`brackets args
458
            (Link.from_path (path :> Paths.Path.t))
6✔
459
      | Poly (polyvars, t) ->
549✔
460
          O.txt ("'" ^ String.concat " '" polyvars ^ ". ") ++ type_expr t
549✔
461
      | Package pkg ->
891✔
462
          enclose ~l:"(" ~r:")"
463
            (O.keyword "module" ++ O.txt " "
891✔
464
            ++ Link.from_path (pkg.path :> Paths.Path.t)
891✔
465
            ++
891✔
466
            match pkg.substitutions with
467
            | [] -> O.noop
120✔
468
            | fst :: lst ->
771✔
469
                O.sp
470
                ++ O.box_hv (O.keyword "with" ++ O.txt " " ++ package_subst fst)
771✔
471
                ++ O.list lst ~f:(fun s ->
771✔
472
                       O.cut
51✔
473
                       ++ (O.box_hv
51✔
474
                          @@ O.txt " " ++ O.keyword "and" ++ O.txt " "
51✔
475
                             ++ package_subst s)))
51✔
476

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

485
  open Type_expression
486

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

496
    val extension : Lang.Extension.t -> Item.t
497

498
    val record : Lang.TypeDecl.Field.t list -> DocumentedSrc.one list
499

500
    val exn : Lang.Exception.t -> Item.t
501

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

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

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

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

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

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

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

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

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

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

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

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

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

894
  open Type_declaration
895

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

922
  open Value
923

924
  (* This chunk of code is responsible for sectioning list of items
925
     according to headings by extracting headings as Items.
926

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

932
    val comment_items : Comment.elements -> Item.t list
933

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

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

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

989
  module Class : sig
990
    val class_ : Lang.Class.t -> Item.t
991

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

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

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

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

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

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

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

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

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

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

1190
  open Class
1191

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

1743
  open Module
1744

1745
  module Page : sig
1746
    val compilation_unit : Lang.Compilation_unit.t -> Document.t
1747

1748
    val page : Lang.Page.t -> Document.t
1749

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

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

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

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

1808
  include Page
1809

1810
  let type_expr = type_expr
1811

1812
  let record = record
1813
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