Skip to content

Commit f965e2a

Browse files
committed
Treat hidden representations differently
Instead of omitting variant constructors where they've got hidden elements in their types, we now show all constructors and just emit a warning when we detect the problem. In addition, also check the fields of records similarly.
1 parent efa5024 commit f965e2a

File tree

7 files changed

+182
-35
lines changed

7 files changed

+182
-35
lines changed

src/document/generator.ml

Lines changed: 0 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -594,27 +594,6 @@ module Make (Syntax : SYNTAX) = struct
594594
O.documentedSrc (cstr ++ O.txt " " ++ O.keyword "of" ++ O.txt " ")
595595
@ record fields
596596

597-
let rec read_typ_exp typ_expr =
598-
let open Lang.TypeExpr in
599-
let open Paths.Path in
600-
match typ_expr with
601-
| Constr (p, ts) ->
602-
is_hidden (p :> Paths.Path.t)
603-
|| List.exists (fun t -> read_typ_exp t) ts
604-
| Poly (_, t) | Alias (t, _) -> read_typ_exp t
605-
| Arrow (_, t, t2) -> read_typ_exp t || read_typ_exp t2
606-
| Tuple ts | Class (_, ts) -> List.exists (fun t -> read_typ_exp t) ts
607-
| _ -> false
608-
609-
let internal_cstr_arg t =
610-
let open Lang.TypeDecl.Constructor in
611-
let open Lang.TypeDecl.Field in
612-
match t.args with
613-
| Tuple type_exprs ->
614-
List.exists (fun type_expr -> read_typ_exp type_expr) type_exprs
615-
| Record fields ->
616-
List.exists (fun field -> read_typ_exp field.type_) fields
617-
618597
let variant cstrs : DocumentedSrc.t =
619598
let constructor id args res =
620599
match Url.from_identifier ~stop_before:true id with
@@ -634,7 +613,6 @@ module Make (Syntax : SYNTAX) = struct
634613
| _ :: _ ->
635614
let rows =
636615
cstrs
637-
|> List.filter (fun cstr -> not (internal_cstr_arg cstr))
638616
|> List.map (fun cstr ->
639617
let open Odoc_model.Lang.TypeDecl.Constructor in
640618
let url, attrs, code =

src/xref2/link.ml

Lines changed: 51 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -365,6 +365,51 @@ and open_ env parent = function
365365
| { Odoc_model__Lang.Open.doc; _ } as open_ ->
366366
{ open_ with doc = comment_docs env parent doc }
367367

368+
let warn_on_hidden_representation (id : Id.Type.t)
369+
(r : Lang.TypeDecl.Representation.t) =
370+
let open Paths.Identifier in
371+
let rec internal_typ_exp typ_expr =
372+
let open Lang.TypeExpr in
373+
let open Paths.Path in
374+
match typ_expr with
375+
| Constr (p, ts) ->
376+
is_hidden (p :> Paths.Path.t)
377+
|| List.exists (fun t -> internal_typ_exp t) ts
378+
| Poly (_, t) | Alias (t, _) -> internal_typ_exp t
379+
| Arrow (_, t, t2) -> internal_typ_exp t || internal_typ_exp t2
380+
| Tuple ts | Class (_, ts) -> List.exists (fun t -> internal_typ_exp t) ts
381+
| _ -> false
382+
in
383+
384+
let internal_cstr_arg t =
385+
let open Lang.TypeDecl.Constructor in
386+
let open Lang.TypeDecl.Field in
387+
match t.args with
388+
| Tuple type_exprs ->
389+
List.exists (fun type_expr -> internal_typ_exp type_expr) type_exprs
390+
| Record fields ->
391+
List.exists (fun field -> internal_typ_exp field.type_) fields
392+
in
393+
394+
let internal_field t =
395+
let open Lang.TypeDecl.Field in
396+
internal_typ_exp t.type_
397+
in
398+
399+
let fmt_cfg = Component.Fmt.{ default with short_paths = true } in
400+
match r with
401+
| Variant constructors ->
402+
if List.exists internal_cstr_arg constructors then
403+
Lookup_failures.report_warning "@[<2>Hidden constructors in type '%a'@]"
404+
Component.Fmt.(model_identifier fmt_cfg)
405+
(id :> Id.any)
406+
| Record fields ->
407+
if List.exists internal_field fields then
408+
Lookup_failures.report_warning "@[<2>Hidden fields in type '%a'@]"
409+
Component.Fmt.(model_identifier fmt_cfg)
410+
(id :> Id.any)
411+
| Extensible -> ()
412+
368413
let rec unit env t =
369414
let open Compilation_unit in
370415
let content =
@@ -877,7 +922,12 @@ and type_decl : Env.t -> Id.Signature.t -> TypeDecl.t -> TypeDecl.t =
877922
| _ -> None
878923
in
879924
let representation =
880-
Opt.map (type_decl_representation env parent) t.representation
925+
Opt.map
926+
(fun r ->
927+
let r' = type_decl_representation env parent r in
928+
warn_on_hidden_representation t.id r';
929+
r')
930+
t.representation
881931
in
882932
let default = { t with source_loc; equation; doc; representation } in
883933
match hidden_path with

test/generators/html/Stop_dead_link_doc.html

Lines changed: 66 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -112,25 +112,87 @@ <h1>Module <code><span>Stop_dead_link_doc</span></code></h1>
112112
<div class="odoc-spec">
113113
<div class="spec type anchored" id="type-another_foo">
114114
<a href="#type-another_foo" class="anchor"></a>
115-
<code><span><span class="keyword">type</span> another_foo</span></code>
115+
<code><span><span class="keyword">type</span> another_foo</span>
116+
<span> = </span>
117+
</code>
118+
<ol>
119+
<li id="type-another_foo.Bar" class="def variant constructor anchored">
120+
<a href="#type-another_foo.Bar" class="anchor"></a>
121+
<code><span>| </span>
122+
<span><span class="constructor">Bar</span>
123+
<span class="keyword">of</span>
124+
<span class="xref-unresolved">{Another_Foo}1.t</span>
125+
</span>
126+
</code>
127+
</li>
128+
</ol>
116129
</div>
117130
</div>
118131
<div class="odoc-spec">
119132
<div class="spec type anchored" id="type-another_bar">
120133
<a href="#type-another_bar" class="anchor"></a>
121-
<code><span><span class="keyword">type</span> another_bar</span></code>
134+
<code><span><span class="keyword">type</span> another_bar</span>
135+
<span> = </span>
136+
</code>
137+
<ol>
138+
<li id="type-another_bar.Bar" class="def variant constructor anchored">
139+
<a href="#type-another_bar.Bar" class="anchor"></a>
140+
<code><span>| </span>
141+
<span><span class="constructor">Bar</span>
142+
<span class="keyword">of</span>
143+
</span><span>{</span>
144+
</code>
145+
<ol>
146+
<li id="type-another_bar.field" class="def record field anchored">
147+
<a href="#type-another_bar.field" class="anchor"></a>
148+
<code>
149+
<span>field : <span class="xref-unresolved">{Another_Foo}1.t</span>
150+
;
151+
</span>
152+
</code>
153+
</li>
154+
</ol><code><span>}</span></code>
155+
</li>
156+
</ol>
122157
</div>
123158
</div>
124159
<div class="odoc-spec">
125160
<div class="spec type anchored" id="type-another_foo_">
126161
<a href="#type-another_foo_" class="anchor"></a>
127-
<code><span><span class="keyword">type</span> another_foo_</span></code>
162+
<code><span><span class="keyword">type</span> another_foo_</span>
163+
<span> = </span>
164+
</code>
165+
<ol>
166+
<li id="type-another_foo_.Bar_" class="def variant constructor
167+
anchored"><a href="#type-another_foo_.Bar_" class="anchor"></a>
168+
<code><span>| </span>
169+
<span><span class="constructor">Bar_</span>
170+
<span class="keyword">of</span> int *
171+
<span class="xref-unresolved">{Another_Foo}1.t</span> * int
172+
</span>
173+
</code>
174+
</li>
175+
</ol>
128176
</div>
129177
</div>
130178
<div class="odoc-spec">
131179
<div class="spec type anchored" id="type-another_bar_">
132180
<a href="#type-another_bar_" class="anchor"></a>
133-
<code><span><span class="keyword">type</span> another_bar_</span></code>
181+
<code><span><span class="keyword">type</span> another_bar_</span>
182+
<span> = </span>
183+
</code>
184+
<ol>
185+
<li id="type-another_bar_.Bar__" class="def variant constructor
186+
anchored"><a href="#type-another_bar_.Bar__" class="anchor"></a>
187+
<code><span>| </span>
188+
<span><span class="constructor">Bar__</span>
189+
<span class="keyword">of</span>
190+
<span><span class="xref-unresolved">{Another_Foo}1.t</span> option
191+
</span>
192+
</span>
193+
</code>
194+
</li>
195+
</ol>
134196
</div>
135197
</div>
136198
</div>

test/generators/latex/Stop_dead_link_doc.tex

Lines changed: 18 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -20,9 +20,23 @@ \section{Module \ocamlinlinecode{Stop\_\allowbreak{}dead\_\allowbreak{}link\_\al
2020
\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[module-Stop_dead_link_doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} option}\label{module-Stop_dead_link_doc-type-bar_.Bar__}\\
2121
\end{ocamltabular}%
2222
\\
23-
\label{module-Stop_dead_link_doc-type-another_foo}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo}\\
24-
\label{module-Stop_dead_link_doc-type-another_bar}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar}\\
25-
\label{module-Stop_dead_link_doc-type-another_foo_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo\_\allowbreak{}}\\
26-
\label{module-Stop_dead_link_doc-type-another_bar_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar\_\allowbreak{}}\\
23+
\label{module-Stop_dead_link_doc-type-another_foo}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo = }\\
24+
\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{\{Another\_\allowbreak{}Foo\}1.\allowbreak{}t}}}\label{module-Stop_dead_link_doc-type-another_foo.Bar}\\
25+
\end{ocamltabular}%
26+
\\
27+
\label{module-Stop_dead_link_doc-type-another_bar}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \{}\\
28+
\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field : \hyperref[xref-unresolved]{\ocamlinlinecode{\{Another\_\allowbreak{}Foo\}1.\allowbreak{}t}};\allowbreak{}}\label{module-Stop_dead_link_doc-type-another_bar.field}\\
29+
\end{ocamltabular}%
30+
\\
31+
\ocamlcodefragment{\}}\label{module-Stop_dead_link_doc-type-another_bar.Bar}\\
32+
\end{ocamlindent}%
33+
\label{module-Stop_dead_link_doc-type-another_foo_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo\_\allowbreak{} = }\\
34+
\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}} \ocamltag{keyword}{of} int * \hyperref[xref-unresolved]{\ocamlinlinecode{\{Another\_\allowbreak{}Foo\}1.\allowbreak{}t}} * int}\label{module-Stop_dead_link_doc-type-another_foo_.Bar_}\\
35+
\end{ocamltabular}%
36+
\\
37+
\label{module-Stop_dead_link_doc-type-another_bar_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar\_\allowbreak{} = }\\
38+
\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{\{Another\_\allowbreak{}Foo\}1.\allowbreak{}t}} option}\label{module-Stop_dead_link_doc-type-another_bar_.Bar__}\\
39+
\end{ocamltabular}%
40+
\\
2741

2842

test/generators/man/Stop_dead_link_doc.3o

Lines changed: 27 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -43,10 +43,33 @@ field : Foo\.t;
4343
| \f[CB]Bar__\fR \f[CB]of\fR Foo\.t option
4444
.br
4545
.sp
46-
\f[CB]type\fR another_foo
46+
\f[CB]type\fR another_foo =
47+
.br
48+
.ti +2
49+
| \f[CB]Bar\fR \f[CB]of\fR {Another_Foo}1\.t
50+
.br
4751
.sp
48-
\f[CB]type\fR another_bar
52+
\f[CB]type\fR another_bar =
53+
.br
54+
.ti +2
55+
| \f[CB]Bar\fR \f[CB]of\fR {
56+
.br
57+
.ti +6
58+
field : {Another_Foo}1\.t;
59+
.br
60+
.ti +4
61+
}
62+
.br
4963
.sp
50-
\f[CB]type\fR another_foo_
64+
\f[CB]type\fR another_foo_ =
65+
.br
66+
.ti +2
67+
| \f[CB]Bar_\fR \f[CB]of\fR int * {Another_Foo}1\.t * int
68+
.br
5169
.sp
52-
\f[CB]type\fR another_bar_
70+
\f[CB]type\fR another_bar_ =
71+
.br
72+
.ti +2
73+
| \f[CB]Bar__\fR \f[CB]of\fR {Another_Foo}1\.t option
74+
.br
75+
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
$ ocamlc -bin-annot -c test.mli
2+
$ odoc compile test.cmti
3+
$ odoc link test.odoc
4+
File "test.odoc":
5+
Warning: Hidden fields in type 'Test.u'
6+
File "test.odoc":
7+
Warning: Hidden constructors in type 'Test.t'
8+
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module Hidden__ : sig
2+
type t
3+
end
4+
5+
type t =
6+
| Variant of int
7+
| Hidden of Hidden__.t
8+
9+
type u =
10+
{ not_hidden : int
11+
; hidden : Hidden__.t }
12+

0 commit comments

Comments
 (0)