diff --git a/src/html/generator.ml b/src/html/generator.ml index 68fcf7366f..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 @@ -321,13 +323,13 @@ 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 ] + let doc = match doc with + | [] -> [] | docs -> - [ - Html.div [ content; div (flow_to_item @@ block ~resolve docs) ]; - ] + let a = [ Html.a_class [ "spec-doc" ] ] in + [ div ~a (flow_to_item @@ block ~resolve docs) ] + in + [ 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 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

-