Skip to content

Commit

Permalink
ocamldoc html: add missing id to signature items
Browse files Browse the repository at this point in the history
This commit adds a new id to classes, modules and module types.
The class id replaces the preexisting name attribute that was intended
to be an id attribute.
  • Loading branch information
Octachron committed Sep 30, 2017
1 parent 55ca4fe commit 9593af5
Show file tree
Hide file tree
Showing 12 changed files with 102 additions and 16 deletions.
3 changes: 3 additions & 0 deletions Changes
Expand Up @@ -22,6 +22,9 @@ be mentioned in the 4.06 section below instead of here.)

### Tools:

- MPR#7635: ocamldoc, add an identifier to module and module type elements
(Florian Angeletti, review by Yawar Amin and Gabriel Scherer)

### Compiler distribution build system

### Internal/compiler-libs changes:
Expand Down
23 changes: 20 additions & 3 deletions ocamldoc/odoc_html.ml
Expand Up @@ -36,6 +36,12 @@ let charset = ref "iso-8859-1"
(** The functions used for naming files and html marks.*)
module Naming =
struct
(** The prefix for modules marks. *)
let mark_module = "MODULE"

(** The prefix for module type marks. *)
let mark_module_type = "MODULETYPE"

(** The prefix for types marks. *)
let mark_type = "TYPE"

Expand Down Expand Up @@ -94,6 +100,12 @@ module Naming =
let (html_file, _) = html_files module_name in
html_file^"#"^(target pref simple_name)

(**return the link target for the given module. *)
let module_target m = target mark_module (Name.simple m.m_name)

(**return the link target for the given module type. *)
let module_type_target mt = target mark_module_type (Name.simple mt.mt_name)

(** Return the link target for the given type. *)
let type_target t = target mark_type (Name.simple t.ty_name)

Expand Down Expand Up @@ -2011,13 +2023,15 @@ class html =
let (html_file, _) = Naming.html_files m.m_name in
let father = Name.father m.m_name in
bs b "\n<pre>";
bp b "<span id=\"%s\">" (Naming.module_target m);
bs b ((self#keyword "module")^" ");
(
if with_link then
bp b "<a href=\"%s\">%s</a>" html_file (Name.simple m.m_name)
else
bs b (Name.simple m.m_name)
);
bs b "</span>" ;
(
match m.m_kind with
Module_functor _ when !html_short_functors ->
Expand All @@ -2041,13 +2055,15 @@ class html =
let (html_file, _) = Naming.html_files mt.mt_name in
let father = Name.father mt.mt_name in
bs b "\n<pre>";
bs b ((self#keyword "module type")^" ");
bp b "<span id=\"%s\">" (Naming.module_type_target mt);
bs b (self#keyword "module type" ^ " ");
(
if with_link then
bp b "<a href=\"%s\">%s</a>" html_file (Name.simple mt.mt_name)
else
bs b (Name.simple mt.mt_name)
);
bs b "</span>";
(match mt.mt_kind with
None -> ()
| Some k ->
Expand Down Expand Up @@ -2181,11 +2197,12 @@ class html =
bs b "\n<pre>";
(* we add a html id, the same as for a type so we can
go directly here when the class name is used as a type name *)
bp b "<span name=\"%s\">"
bp b "<span id=\"%s\">"
(Naming.type_target
{ ty_name = c.cl_name ;
ty_info = None ; ty_parameters = [] ;
ty_kind = Type_abstract ; ty_private = Asttypes.Public; ty_manifest = None ;
ty_kind = Type_abstract ; ty_private = Asttypes.Public;
ty_manifest = None ;
ty_loc = Odoc_info.dummy_loc ;
ty_code = None ;
}
Expand Down
Expand Up @@ -15,7 +15,7 @@
&nbsp;</div>
<h1>Module <a href="type_Documentation_tags.html">Documentation_tags</a></h1>

<pre><span class="keyword">module</span> Documentation_tags: <code class="code"><span class="keyword">sig</span></code> <a href="Documentation_tags.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<pre><span id="MODULEDocumentation_tags"><span class="keyword">module</span> Documentation_tags</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Documentation_tags.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<div class="info-desc">
<p>Test the html rendering of ocamldoc documentation tags</p>
</div>
Expand Down
Expand Up @@ -17,7 +17,7 @@
&nbsp;</div>
<h1>Module <a href="type_Inline_records.html">Inline_records</a></h1>

<pre><span class="keyword">module</span> Inline_records: <code class="code"><span class="keyword">sig</span></code> <a href="Inline_records.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<pre><span id="MODULEInline_records"><span class="keyword">module</span> Inline_records</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Inline_records.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<div class="info-desc">
<p>This test focuses on the printing of documentation for inline record
within the latex generator.</p>
Expand Down
13 changes: 13 additions & 0 deletions testsuite/tests/tool-ocamldoc-html/Item_ids.mli
@@ -0,0 +1,13 @@
(** Check that all toplevel items are given a unique id. *)

exception Ex
type t
val x: t
type ext = ..
type ext += A
class c: object end
class type ct= object end
[@@@attribute]
module M: sig end
module type s = sig end

53 changes: 53 additions & 0 deletions testsuite/tests/tool-ocamldoc-html/Item_ids.reference
@@ -0,0 +1,53 @@
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN">
<html>
<head>
<link rel="stylesheet" href="style.css" type="text/css">
<meta content="text/html; charset=iso-8859-1" http-equiv="Content-Type">
<meta name="viewport" content="width=device-width, initial-scale=1">
<link rel="Start" href="index.html">
<link rel="Up" href="index.html">
<link title="Index of types" rel=Appendix href="index_types.html">
<link title="Index of extensions" rel=Appendix href="index_extensions.html">
<link title="Index of exceptions" rel=Appendix href="index_exceptions.html">
<link title="Index of values" rel=Appendix href="index_values.html">
<link title="Index of classes" rel=Appendix href="index_classes.html">
<link title="Index of class types" rel=Appendix href="index_class_types.html">
<link title="Index of modules" rel=Appendix href="index_modules.html">
<link title="Index of module types" rel=Appendix href="index_module_types.html">
<link title="Item_ids" rel="Chapter" href="Item_ids.html"><title>Item_ids</title>
</head>
<body>
<div class="navbar">&nbsp;<a class="up" href="index.html" title="Index">Up</a>
&nbsp;</div>
<h1>Module <a href="type_Item_ids.html">Item_ids</a></h1>

<pre><span id="MODULEItem_ids"><span class="keyword">module</span> Item_ids</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Item_ids.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<div class="info-desc">
<p>Check that all toplevel items are given a unique id.</p>
</div>
</div>
<hr width="100%">

<pre><span id="EXCEPTIONEx"><span class="keyword">exception</span> Ex</span></pre>

<pre><span id="TYPEt"><span class="keyword">type</span> <code class="type"></code>t</span> </pre>


<pre><span id="VALx"><span class="keyword">val</span> x</span> : <code class="type"><a href="Item_ids.html#TYPEt">t</a></code></pre>
<pre><span id="TYPEext"><span class="keyword">type</span> <code class="type"></code>ext</span> = ..</pre>

<pre><code><span class="keyword">type</span> <code class="type"></code><a href="Item_ids.html#TYPEext">ext</a> += </code></pre><table class="typetable">
<tr>
<td align="left" valign="top" >
<code><span class="keyword">|</span></code></td>
<td align="left" valign="top" >
<code><span id="EXTENSIONA">A</span></code></td>

</tr></table>



<pre><span id="TYPEc"><span class="keyword">class</span> <a href="Item_ids.c-c.html">c</a></span> : <code class="type"></code><code class="code"><span class="keyword">object</span></code> <a href="Item_ids.c-c.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="TYPEct"><span class="keyword">class type</span> <a href="Item_ids.ct-c.html">ct</a></span> = <code class="code"><span class="keyword">object</span></code> <a href="Item_ids.ct-c.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="MODULEM"><span class="keyword">module</span> <a href="Item_ids.M.html">M</a></span>: <code class="code"><span class="keyword">sig</span></code> <a href="Item_ids.M.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="MODULETYPEs"><span class="keyword">module type</span> <a href="Item_ids.s-c.html">s</a></span> = <code class="code"><span class="keyword">sig</span></code> <a href="Item_ids.s-c.html">..</a> <code class="code"><span class="keyword">end</span></code></pre></body></html>
6 changes: 3 additions & 3 deletions testsuite/tests/tool-ocamldoc-html/Linebreaks.reference
Expand Up @@ -20,7 +20,7 @@
&nbsp;</div>
<h1>Module <a href="type_Linebreaks.html">Linebreaks</a></h1>

<pre><span class="keyword">module</span> Linebreaks: <code class="code"><span class="keyword">sig</span></code> <a href="Linebreaks.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<pre><span id="MODULELinebreaks"><span class="keyword">module</span> Linebreaks</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Linebreaks.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<div class="info-desc">
<p>This file tests the encoding of linebreak inside OCaml code by the
ocamldoc html backend.</p>
Expand Down Expand Up @@ -98,8 +98,8 @@


<pre><span id="VALx"><span class="keyword">val</span> x</span> : <code class="type"><a href="Linebreaks.html#TYPEa">a</a></code></pre>
<pre><span class="keyword">module</span> <a href="Linebreaks.S.html">S</a>: <code class="code"><span class="keyword">sig</span></code> <a href="Linebreaks.S.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span class="keyword">module type</span> <a href="Linebreaks.s-c.html">s</a> = <code class="code"><span class="keyword">sig</span></code> <a href="Linebreaks.s-c.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="MODULES"><span class="keyword">module</span> <a href="Linebreaks.S.html">S</a></span>: <code class="code"><span class="keyword">sig</span></code> <a href="Linebreaks.S.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="MODULETYPEs"><span class="keyword">module type</span> <a href="Linebreaks.s-c.html">s</a></span> = <code class="code"><span class="keyword">sig</span></code> <a href="Linebreaks.s-c.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="TYPEd"><span class="keyword">class type</span> <a href="Linebreaks.d-c.html">d</a></span> = <code class="code"><span class="keyword">object</span></code> <a href="Linebreaks.d-c.html">..</a> <code class="code"><span class="keyword">end</span></code></pre>
<pre><span id="EXCEPTIONE"><span class="keyword">exception</span> E</span> <span class="keyword">of</span> <code>{</code><table class="typetable">
<tr>
Expand Down
6 changes: 3 additions & 3 deletions testsuite/tests/tool-ocamldoc-html/Loop.reference
Expand Up @@ -14,7 +14,7 @@
&nbsp;</div>
<h1>Module <a href="type_Loop.html">Loop</a></h1>

<pre><span class="keyword">module</span> Loop: <code class="code"><span class="keyword">sig</span></code> <a href="Loop.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">
<pre><span id="MODULELoop"><span class="keyword">module</span> Loop</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Loop.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">

<pre><span class="keyword">module</span> <a href="Loop.A.html">A</a>: <code class="type"><a href="Loop.B.html">B</a></code></pre>
<pre><span class="keyword">module</span> <a href="Loop.B.html">B</a>: <code class="type"><a href="Loop.A.html">A</a></code></pre></body></html>
<pre><span id="MODULEA"><span class="keyword">module</span> <a href="Loop.A.html">A</a></span>: <code class="type"><a href="Loop.B.html">B</a></code></pre>
<pre><span id="MODULEB"><span class="keyword">module</span> <a href="Loop.B.html">B</a></span>: <code class="type"><a href="Loop.A.html">A</a></code></pre></body></html>
Expand Up @@ -14,9 +14,9 @@
&nbsp;</div>
<h1>Module <a href="type_Module_whitespace.html">Module_whitespace</a></h1>

<pre><span class="keyword">module</span> Module_whitespace: <code class="code"><span class="keyword">sig</span></code> <a href="Module_whitespace.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">
<pre><span id="MODULEModule_whitespace"><span class="keyword">module</span> Module_whitespace</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Module_whitespace.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">

<pre><span class="keyword">module</span> <a href="Module_whitespace.M.html">M</a>: <code class="type">Set.Make</code><code class="code">(</code><code class="code"><span class="keyword">sig</span></code></pre><div class="sig_block">
<pre><span id="MODULEM"><span class="keyword">module</span> <a href="Module_whitespace.M.html">M</a></span>: <code class="type">Set.Make</code><code class="code">(</code><code class="code"><span class="keyword">sig</span></code></pre><div class="sig_block">
<pre><span id="TYPEt"><span class="keyword">type</span> <code class="type"></code>t</span> = <code class="type">int</code> </pre>


Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/tool-ocamldoc-html/No_preamble.reference
Expand Up @@ -15,7 +15,7 @@
&nbsp;</div>
<h1>Module <a href="type_No_preamble.html">No_preamble</a></h1>

<pre><span class="keyword">module</span> No_preamble: <code class="code"><span class="keyword">sig</span></code> <a href="No_preamble.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">
<pre><span id="MODULENo_preamble"><span class="keyword">module</span> No_preamble</span>: <code class="code"><span class="keyword">sig</span></code> <a href="No_preamble.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">

<pre><span id="VALx"><span class="keyword">val</span> x</span> : <code class="type">unit</code></pre><div class="info ">
<div class="info-desc">
Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/tool-ocamldoc-html/Paragraph.reference
Expand Up @@ -15,7 +15,7 @@
&nbsp;</div>
<h1>Module <a href="type_Paragraph.html">Paragraph</a></h1>

<pre><span class="keyword">module</span> Paragraph: <code class="code"><span class="keyword">sig</span></code> <a href="Paragraph.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<pre><span id="MODULEParagraph"><span class="keyword">module</span> Paragraph</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Paragraph.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<div class="info-desc">
<p>This file tests the generation of paragraph within module comments.</p>

Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/tool-ocamldoc-html/Variants.reference
Expand Up @@ -15,7 +15,7 @@
&nbsp;</div>
<h1>Module <a href="type_Variants.html">Variants</a></h1>

<pre><span class="keyword">module</span> Variants: <code class="code"><span class="keyword">sig</span></code> <a href="Variants.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<pre><span id="MODULEVariants"><span class="keyword">module</span> Variants</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Variants.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><div class="info module top">
<div class="info-desc">
<p>This test is here to check the latex code generated for variants</p>
</div>
Expand Down

0 comments on commit 9593af5

Please sign in to comment.