diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml
index b06bd8782..c5b610db9 100644
--- a/ocamldoc/odoc_html.ml
+++ b/ocamldoc/odoc_html.ml
@@ -125,7 +125,6 @@ class ocaml_code =
html_code
end
-
(** Generation of html code from text structures. *)
class text =
object (self)
@@ -136,6 +135,29 @@ class text =
make some replacements (double newlines replaced by
). *)
method escape s = Odoc_ocamlhtml.escape_base s
+
+ method keep_alpha_num s =
+ let len = String.length s in
+ let buf = Buffer.create len in
+ for i = 0 to len - 1 do
+ match s.[i] with
+ 'a'..'z' | 'A'..'Z' | '0'..'9' -> Buffer.add_char buf s.[i]
+ | _ -> ()
+ done;
+ Buffer.contents buf
+
+ (** Create a label for the associated title.
+ If a label is given, use the label, or else create a mark
+ from the title level and the first sentence of the title.*)
+ method create_title_label (n,label_opt,t) =
+ match label_opt with
+ Some s -> s
+ | None ->
+ let t2 = Odoc_info.first_sentence_of_text t in
+ let s = Odoc_info.string_of_text t2 in
+ let s2 = self#keep_alpha_num s in
+ Printf.sprintf "%d%s" n s2
+
(** Return the html code corresponding to the [text] parameter. *)
method html_of_text t = String.concat "" (List.map self#html_of_text_element t)
@@ -206,11 +228,7 @@ class text =
method html_of_Title n label_opt t =
let css_class = "title"^(string_of_int n) in
"
\n"^
- (
- match label_opt with
- None -> ""
- | Some l -> ""
- )^
+ ""^
"
\n"^
""^(self#html_of_text t)^"\n"^
@@ -496,7 +514,7 @@ class html =
val mutable list_class_types = []
(** The header of pages. Must be prepared by the [prepare_header] method.*)
- val mutable header = fun ?(nav=None) -> fun _ -> ""
+ val mutable header = fun ?(nav=None) -> fun ?(comments=[]) -> fun _ -> ""
(** Init the style. *)
method init_style =
@@ -528,11 +546,11 @@ class html =
(self#escape s)
(** Get the page header. *)
- method header ?nav title = header ?nav title
+ method header ?nav ?comments title = header ?nav ?comments title
(** A function to build the header of pages. *)
method prepare_header module_list =
- let f ?(nav=None) t =
+ let f ?(nav=None) ?(comments=[]) t =
let link_if_not_empty l m url =
match l with
[] -> ""
@@ -579,12 +597,54 @@ class html =
module_list
)
)^
+ (self#html_sections_links comments)^
" |