From 2ac92639fa5f62d36ed86be9d793e4c953ad6ce4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Daniel=20B=C3=BCnzli?= Date: Mon, 15 Feb 2021 17:51:34 +0100 Subject: [PATCH 1/4] Regularize declaration markup. This no longer special cases the markup for declarations that have no docstring. Before it would be: div (div.spec div) # With docstring div.spec # Without docstring With this patch this becomes: div (div.spec div) # With docstring div (div.spec) # Without docstring The regularity simplifies stylesheets development. --- src/html/generator.ml | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/src/html/generator.ml b/src/html/generator.ml index 68fcf7366f..001ee1a0de 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -321,13 +321,11 @@ and items ~resolve l : item Html.elt list = let a = class_of_kind kind @ anchor_attrib in let content = anchor_link @ documentedSrc ~resolve content in let elts = - let content = div ~a content in - match doc with - | [] -> [ content ] - | docs -> - [ - Html.div [ content; div (flow_to_item @@ block ~resolve docs) ]; - ] + let doc = match doc with + | [] -> [] + | docs -> [ div (flow_to_item @@ block ~resolve docs) ] + in + [ div (div ~a content :: doc) ] in (continue_with [@tailcall]) rest elts and items l = walk_items ~only_text:(is_only_text l) [] l in From acd184cfab1d442a36c6e76fb4eb4e04a44afd1a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Daniel=20B=C3=BCnzli?= Date: Mon, 15 Feb 2021 18:14:24 +0100 Subject: [PATCH 2/4] Classify the docstring div of declarations. `div (div.spec div)` becomes `div (div.spec div.spec-doc)`. --- src/html/generator.ml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/html/generator.ml b/src/html/generator.ml index 001ee1a0de..8880bf7e4d 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -323,7 +323,9 @@ and items ~resolve l : item Html.elt list = let elts = let doc = match doc with | [] -> [] - | docs -> [ div (flow_to_item @@ block ~resolve docs) ] + | docs -> + let a = [ Html.a_class [ "spec-doc" ] ] in + [ div ~a (flow_to_item @@ block ~resolve docs) ] in [ div (div ~a content :: doc) ] in From 7e8e8ad38d85a13e0d78e61254f448fee8650a1f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Daniel=20B=C3=BCnzli?= Date: Mon, 15 Feb 2021 18:15:43 +0100 Subject: [PATCH 3/4] Except for headers and .mlds classify all children of .odoc-content. Unattached trees are classified by `.odoc-unattached` Include divs is classified by `.odoc-include` Declarations are classified by `.odoc-spec` --- src/html/generator.ml | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/src/html/generator.ml b/src/html/generator.ml index 8880bf7e4d..bf78af7d7a 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -278,7 +278,9 @@ and items ~resolve l : item Html.elt list = let content = flow_to_item @@ block ~resolve text in let elts = if only_text then content - else [ Html.aside (content :> any Html.elt list) ] + else + let a = [ Html.a_class [ "odoc-unattached" ] ] in + [ Html.aside ~a (content :> any Html.elt list) ] in elts |> (continue_with [@tailcall]) rest | Heading h :: rest -> @@ -308,7 +310,7 @@ and items ~resolve l : item Html.elt list = let a = class_of_kind kind @ anchor_attrib in (* TODO : Why double div ??? *) [ - Html.div + Html.div ~a:[ Html.a_class [ "odoc-include" ] ] [ Html.div ~a ( anchor_link @@ -327,7 +329,7 @@ and items ~resolve l : item Html.elt list = let a = [ Html.a_class [ "spec-doc" ] ] in [ div ~a (flow_to_item @@ block ~resolve docs) ] in - [ div (div ~a content :: doc) ] + [ div ~a: [ Html.a_class [ "odoc-spec" ]] (div ~a content :: doc) ] in (continue_with [@tailcall]) rest elts and items l = walk_items ~only_text:(is_only_text l) [] l in From 1ca3e983b622accb2df29dbb120453e7b3e1b880 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Daniel=20B=C3=BCnzli?= Date: Thu, 18 Feb 2021 09:35:46 +0100 Subject: [PATCH 4/4] Promote expect tests to new markup structure. --- .../Include/index.html | 92 +- .../Module/index.html | 88 +- .../Section/index.html | 12 +- .../Val/index.html | 14 +- .../expect/test_package+ml/Alias/X/index.html | 4 +- .../expect/test_package+ml/Alias/index.html | 12 +- .../expect/test_package+ml/Bugs/index.html | 10 +- .../test_package+ml/Bugs_post_406/index.html | 12 +- .../test_package+ml/Bugs_pre_410/index.html | 10 +- .../expect/test_package+ml/Class/index.html | 54 +- .../test_package+ml/External/index.html | 4 +- .../expect/test_package+ml/Functor/index.html | 42 +- .../expect/test_package+ml/Include/index.html | 92 +- .../test_package+ml/Include2/index.html | 12 +- .../Include_sections/index.html | 100 +- .../module-type-Something/index.html | 20 +- .../test_package+ml/Interlude/index.html | 32 +- .../expect/test_package+ml/Labels/index.html | 130 +- .../expect/test_package+ml/Markup/index.html | 32 +- .../expect/test_package+ml/Module/index.html | 88 +- .../Nested/F/argument-1-Arg1/index.html | 8 +- .../Nested/F/argument-2-Arg2/index.html | 4 +- .../test_package+ml/Nested/F/index.html | 16 +- .../test_package+ml/Nested/X/index.html | 8 +- .../Nested/class-inherits/index.html | 6 +- .../test_package+ml/Nested/class-z/index.html | 20 +- .../expect/test_package+ml/Nested/index.html | 22 +- .../Nested/module-type-Y/index.html | 8 +- .../test_package+ml/Ocamlary/index.html | 1366 +++++++++------- .../test_package+ml/Recent/X/index.html | 24 +- .../expect/test_package+ml/Recent/index.html | 356 +++-- .../test_package+ml/Recent_impl/index.html | 30 +- .../expect/test_package+ml/Section/index.html | 12 +- .../expect/test_package+ml/Stop/index.html | 18 +- .../expect/test_package+ml/Type/index.html | 894 ++++++----- .../expect/test_package+ml/Val/index.html | 14 +- .../expect/test_package+re/Alias/X/index.html | 4 +- .../expect/test_package+re/Alias/index.html | 12 +- .../expect/test_package+re/Bugs/index.html | 10 +- .../test_package+re/Bugs_post_406/index.html | 12 +- .../test_package+re/Bugs_pre_410/index.html | 10 +- .../expect/test_package+re/Class/index.html | 54 +- .../test_package+re/External/index.html | 4 +- .../expect/test_package+re/Functor/index.html | 42 +- .../expect/test_package+re/Include/index.html | 92 +- .../test_package+re/Include2/index.html | 12 +- .../Include_sections/index.html | 100 +- .../module-type-Something/index.html | 20 +- .../test_package+re/Interlude/index.html | 32 +- .../expect/test_package+re/Labels/index.html | 132 +- .../expect/test_package+re/Markup/index.html | 32 +- .../expect/test_package+re/Module/index.html | 88 +- .../Nested/F/argument-1-Arg1/index.html | 8 +- .../Nested/F/argument-2-Arg2/index.html | 4 +- .../test_package+re/Nested/F/index.html | 16 +- .../test_package+re/Nested/X/index.html | 8 +- .../Nested/class-inherits/index.html | 6 +- .../test_package+re/Nested/class-z/index.html | 20 +- .../expect/test_package+re/Nested/index.html | 22 +- .../Nested/module-type-Y/index.html | 8 +- .../test_package+re/Ocamlary/index.html | 1386 ++++++++++------- .../test_package+re/Recent/X/index.html | 24 +- .../expect/test_package+re/Recent/index.html | 364 +++-- .../test_package+re/Recent_impl/index.html | 30 +- .../expect/test_package+re/Section/index.html | 12 +- .../expect/test_package+re/Stop/index.html | 18 +- .../expect/test_package+re/Type/index.html | 908 ++++++----- .../expect/test_package+re/Val/index.html | 14 +- 68 files changed, 4144 insertions(+), 3026 deletions(-) diff --git a/test/html/expect/test_package+custom_theme,ml/Include/index.html b/test/html/expect/test_package+custom_theme,ml/Include/index.html index 217991ce20..4302345d69 100644 --- a/test/html/expect/test_package+custom_theme,ml/Include/index.html +++ b/test/html/expect/test_package+custom_theme,ml/Include/index.html @@ -23,112 +23,138 @@

-
- module type Not_inlined = sig ... end +
+
+ module type Not_inlined = sig ... end +
-
+
include Not_inlined -
- type t +
+
+ type t +
-
- module type Inlined = sig ... end +
+
+ module type Inlined = sig ... end +
-
+
-
- type u +
+
+ type u +
-
- module type Not_inlined_and_closed = sig ... end +
+
+ module type Not_inlined_and_closed = sig ... end +
-
+
include Not_inlined_and_closed -
- type v +
+
+ type v +
-
- module type Not_inlined_and_opened = sig ... end +
+
+ module type Not_inlined_and_opened = sig ... end +
-
+
include Not_inlined_and_opened -
- type w +
+
+ type w +
-
- module type Inherent_Module = sig ... end +
+
+ module type Inherent_Module = sig ... end +
-
+
include Inherent_Module -
- val a : t +
+
+ val a : t +
-
- module type Dorminant_Module = sig ... end +
+
+ module type Dorminant_Module = sig ... end +
-
+
include Dorminant_Module -
+
include Inherent_Module -
- val a : t +
+
+ val a : t +
-
- val a : u +
+
+ val a : u +
diff --git a/test/html/expect/test_package+custom_theme,ml/Module/index.html b/test/html/expect/test_package+custom_theme,ml/Module/index.html index e27452f7f2..a2968b9a1b 100644 --- a/test/html/expect/test_package+custom_theme,ml/Module/index.html +++ b/test/html/expect/test_package+custom_theme,ml/Module/index.html @@ -26,57 +26,85 @@

-
+
val foo : unit
-
+

The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See https://caml.inria.fr/mantis/view.php?id=7701.

-
- module type S = sig ... end +
+
+ module type S = sig ... end +
-
- module type S1 +
+
+ module type S1 +
-
- module type S2 = S +
+
+ module type S2 = S +
-
- module type S3 = S with type t = int and type u = string +
+
+ module type S3 = S with type t = int and type u = string +
-
- module type S4 = S with type t := int +
+
+ module type S4 = S with type t := int +
-
- module type S5 = S with type 'a v := 'a list +
+
+ module type S5 = S with type 'a v := 'a list +
-
- type ('a, 'b) result +
+
+ type ('a, 'b) result +
-
- module type S6 = S with type ('a, 'b) w := ('a'b) result +
+
+ module type S6 = S with type ('a, 'b) w := ('a'b) result +
-
- module M' : sig ... end +
+
+ module M' : sig ... end +
-
- module type S7 = S with module M = M' +
+
+ module type S7 = S with module M = M' +
-
- module type S8 = S with module M := M' +
+
+ module type S8 = S with module M := M' +
-
- module type S9 = module type of M' +
+
+ module type S9 = module type of M' +
-
- module Mutually : sig ... end +
+
+ module Mutually : sig ... end +
-
- module Recursive : sig ... end +
+
+ module Recursive : sig ... end +
diff --git a/test/html/expect/test_package+custom_theme,ml/Section/index.html b/test/html/expect/test_package+custom_theme,ml/Section/index.html index b16d2261b7..009d17ffa7 100644 --- a/test/html/expect/test_package+custom_theme,ml/Section/index.html +++ b/test/html/expect/test_package+custom_theme,ml/Section/index.html @@ -62,7 +62,7 @@

Text only

-