Skip to content

Commit cc2445a

Browse files
committed
Handle the top-comment in class signatures
Like module signatures, extract the top-comment from the loader and pass it through. Render it the same way as modules.
1 parent 50e6c24 commit cc2445a

File tree

19 files changed

+55
-38
lines changed

19 files changed

+55
-38
lines changed

src/document/generator.ml

Lines changed: 14 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,9 @@ let attach_expansion ?(status = `Default) (eq, o, e) page text =
8181
DocumentedSrc.
8282
[ Alternative (Expansion { summary; url; status; expansion }) ]
8383

84+
let doc_of_expansion ~decl_doc ~expansion_doc =
85+
Comment.standalone decl_doc @ Comment.standalone expansion_doc
86+
8487
include Generator_signatures
8588

8689
module Make (Syntax : SYNTAX) = struct
@@ -948,7 +951,7 @@ module Make (Syntax : SYNTAX) = struct
948951
loop rest (List.rev_append items acc_items) )
949952
in
950953
(* FIXME: use [t.self] *)
951-
loop c.items []
954+
(c.doc, loop c.items [])
952955

953956
let rec class_decl (cd : Odoc_model.Lang.Class.decl) =
954957
match cd with
@@ -977,10 +980,12 @@ module Make (Syntax : SYNTAX) = struct
977980
match t.expansion with
978981
| None -> (O.documentedSrc @@ O.txt name, None)
979982
| Some csig ->
980-
let doc = Comment.standalone t.doc in
981-
let items = class_signature csig in
983+
let expansion_doc, items = class_signature csig in
982984
let url = Url.Path.from_identifier t.id in
983-
let header = format_title `Class (make_name_from_path url) @ doc in
985+
let header =
986+
format_title `Class (make_name_from_path url)
987+
@ doc_of_expansion ~decl_doc:t.doc ~expansion_doc
988+
in
984989
let page = { Page.title = name; header; items; url } in
985990
(O.documentedSrc @@ path url [ inline @@ Text name ], Some page)
986991
in
@@ -1013,9 +1018,11 @@ module Make (Syntax : SYNTAX) = struct
10131018
| None -> (O.documentedSrc @@ O.txt name, None)
10141019
| Some csig ->
10151020
let url = Url.Path.from_identifier t.id in
1016-
let doc = Comment.standalone t.doc in
1017-
let items = class_signature csig in
1018-
let header = format_title `Cty (make_name_from_path url) @ doc in
1021+
let expansion_doc, items = class_signature csig in
1022+
let header =
1023+
format_title `Cty (make_name_from_path url)
1024+
@ doc_of_expansion ~decl_doc:t.doc ~expansion_doc
1025+
in
10191026
let page = { Page.title = name; header; items; url } in
10201027
(O.documentedSrc @@ path url [ inline @@ Text name ], Some page)
10211028
in
@@ -1069,9 +1076,6 @@ module Make (Syntax : SYNTAX) = struct
10691076
| `Module (_, name) when ModuleName.is_internal name -> true
10701077
| _ -> false
10711078

1072-
let doc_of_expansion ~decl_doc ~expansion_doc =
1073-
Comment.standalone decl_doc @ Comment.standalone expansion_doc
1074-
10751079
let rec signature (s : Lang.Signature.t) =
10761080
let rec loop l acc_items =
10771081
match l with

src/loader/cmi.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -755,7 +755,7 @@ let rec read_class_signature env parent params =
755755
List.map (read_method env parent csig.csig_concr) methods
756756
in
757757
let items = constraints @ instance_variables @ methods in
758-
Signature {self; items}
758+
Signature {self; items; doc = []}
759759
| Cty_arrow _ -> assert false
760760

761761
let rec read_virtual = function

src/loader/cmt.ml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -176,7 +176,8 @@ and read_class_signature env parent params cltyp =
176176
[] csig.csig_fields
177177
in
178178
let items = constraints @ List.rev items in
179-
Signature {self; items}
179+
let items, doc = Doc_attr.extract_top_comment_class items in
180+
Signature {self; items; doc}
180181
| Tcty_arrow _ -> assert false
181182
#if OCAML_MAJOR = 4 && OCAML_MINOR >= 06
182183
| Tcty_open _ -> assert false
@@ -263,7 +264,8 @@ and read_class_structure env parent params cl =
263264
[] cstr.cstr_fields
264265
in
265266
let items = constraints @ List.rev items in
266-
Signature {self; items}
267+
let items, doc = Doc_attr.extract_top_comment_class items in
268+
Signature {self; items; doc}
267269
| Tcl_fun _ -> assert false
268270
| Tcl_let(_, _, _, cl) -> read_class_structure env parent params cl
269271
| Tcl_constraint(cl, None, _, _, _) -> read_class_structure env parent params cl

src/loader/cmti.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -383,7 +383,8 @@ and read_class_signature env parent label_parent cltyp =
383383
[] csig.csig_fields
384384
in
385385
let items = List.rev items in
386-
Signature {self; items}
386+
let items, doc = Doc_attr.extract_top_comment_class items in
387+
Signature {self; items; doc}
387388
| Tcty_arrow _ -> assert false
388389
#if OCAML_MAJOR = 4 && OCAML_MINOR >= 06 && OCAML_MINOR < 08
389390
| Tcty_open (_, _, _, _, cty) -> read_class_signature env parent label_parent cty

src/loader/doc_attr.ml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -132,3 +132,8 @@ let extract_top_comment items =
132132
match items with
133133
| Lang.Signature.Comment (`Docs doc) :: tl -> (tl, doc)
134134
| _ -> (items, empty)
135+
136+
let extract_top_comment_class items =
137+
match items with
138+
| Lang.ClassSignature.Comment (`Docs doc) :: tl -> (tl, doc)
139+
| _ -> items, empty

src/loader/doc_attr.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -54,3 +54,7 @@ val standalone_multiple :
5454
val extract_top_comment :
5555
Lang.Signature.item list -> Lang.Signature.item list * Comment.docs
5656
(** Extract the first comment of a signature. Returns the remaining items. *)
57+
58+
val extract_top_comment_class :
59+
Lang.ClassSignature.item list -> Lang.ClassSignature.item list * Comment.docs
60+
(** Extract the first comment of a class signature. Returns the remaining items. *)

src/model/lang.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -334,7 +334,7 @@ and ClassSignature : sig
334334
| Inherit of ClassType.expr
335335
| Comment of Comment.docs_or_stop
336336

337-
type t = { self : TypeExpr.t option; items : item list }
337+
type t = { self : TypeExpr.t option; items : item list; doc : Comment.docs }
338338
end =
339339
ClassSignature
340340

src/xref2/compile.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -151,6 +151,7 @@ and class_signature env parent c =
151151
| Comment c -> Comment c
152152
in
153153
{
154+
c with
154155
self = Opt.map (type_expression env container) c.self;
155156
items = List.map map_item c.items;
156157
}

src/xref2/component.ml

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -377,7 +377,7 @@ and ClassSignature : sig
377377
| Inherit of ClassType.expr
378378
| Comment of CComment.docs_or_stop
379379

380-
type t = { self : TypeExpr.t option; items : item list }
380+
type t = { self : TypeExpr.t option; items : item list; doc : CComment.docs }
381381
end =
382382
ClassSignature
383383

@@ -2177,7 +2177,11 @@ module Of_Lang = struct
21772177
| Comment c -> Comment (docs_or_stop ident_map c))
21782178
sg.items
21792179
in
2180-
{ ClassSignature.self = Opt.map (type_expression ident_map) sg.self; items }
2180+
{
2181+
ClassSignature.self = Opt.map (type_expression ident_map) sg.self;
2182+
items;
2183+
doc = docs ident_map sg.doc;
2184+
}
21812185

21822186
and method_ ident_map m =
21832187
let open Odoc_model.Lang.Method in

src/xref2/component.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -351,7 +351,7 @@ and ClassSignature : sig
351351
| Inherit of ClassType.expr
352352
| Comment of CComment.docs_or_stop
353353

354-
type t = { self : TypeExpr.t option; items : item list }
354+
type t = { self : TypeExpr.t option; items : item list; doc : CComment.docs }
355355
end
356356

357357
and Method : sig

0 commit comments

Comments
 (0)