summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2002-06-04 09:21:38 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2002-06-04 09:21:38 +0000
commitbb54244c9f293cc9156f6c1f97816f34e50ff506 (patch)
tree1a0469e4d9d2ec24858a9c711ad4b4348e72fe1b
parent6f33a78438ef5e9aed6e825b0bda22f49ab7278f (diff)
on enlève les titres dans les premières phrases pour les index et les titres LaTeX comme module Foo : titre
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4874 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--ocamldoc/Changes.txt3
-rw-r--r--ocamldoc/odoc_html.ml7
-rw-r--r--ocamldoc/odoc_info.ml3
-rw-r--r--ocamldoc/odoc_info.mli3
-rw-r--r--ocamldoc/odoc_latex.ml5
-rw-r--r--ocamldoc/odoc_misc.ml37
-rw-r--r--ocamldoc/odoc_misc.mli3
7 files changed, 58 insertions, 3 deletions
diff --git a/ocamldoc/Changes.txt b/ocamldoc/Changes.txt
index cda387e50..c07c57b72 100644
--- a/ocamldoc/Changes.txt
+++ b/ocamldoc/Changes.txt
@@ -1,4 +1,7 @@
Next release :
+ - no titles nor lists in first sentence of text in indexes and latex titles
+ - only one table for the titles in HTML output
+ - fix of bad comment association for types in .ml files
- dumps now contain a magic number, checked when dumps are loaded
- new option -o to use with texi, latex and dot generators
- new .code CSS class used
diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml
index 74b8f617a..d8371db6a 100644
--- a/ocamldoc/odoc_html.ml
+++ b/ocamldoc/odoc_html.ml
@@ -374,7 +374,8 @@ class virtual info =
(self#html_of_custom info.M.i_custom)^
"</div>\n"
- (** Return html code for the first sentence of a description. *)
+ (** Return html code for the first sentence of a description.
+ The titles and lists in this first sentence has been removed.*)
method html_of_info_first_sentence info_opt =
match info_opt with
None -> ""
@@ -386,7 +387,9 @@ class virtual info =
(match info.M.i_desc with
None -> ""
| Some d when d = [Odoc_info.Raw ""] -> ""
- | Some d -> (self#html_of_text (Odoc_info.first_sentence_of_text d))^"\n"
+ | Some d -> (self#html_of_text
+ (Odoc_info.text_no_title_no_list
+ (Odoc_info.first_sentence_of_text d)))^"\n"
)^
(if dep then "</font>" else "") ^
"</div>\n"
diff --git a/ocamldoc/odoc_info.ml b/ocamldoc/odoc_info.ml
index 5526bc314..c4d9a4f1f 100644
--- a/ocamldoc/odoc_info.ml
+++ b/ocamldoc/odoc_info.ml
@@ -135,8 +135,11 @@ let string_of_attribute att = Odoc_str.string_of_attribute att
let string_of_method m = Odoc_str.string_of_method m
let first_sentence_of_text = Odoc_misc.first_sentence_of_text
+
let first_sentence_and_rest_of_text = Odoc_misc.first_sentence_and_rest_of_text
+let text_no_title_no_list = Odoc_misc.text_no_title_no_list
+
let create_index_lists = Odoc_misc.create_index_lists
let remove_option = Odoc_misc.remove_option
diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli
index ff87428fe..bc9896480 100644
--- a/ocamldoc/odoc_info.mli
+++ b/ocamldoc/odoc_info.mli
@@ -638,6 +638,9 @@ val first_sentence_of_text : Odoc_types.text -> Odoc_types.text
val first_sentence_and_rest_of_text :
Odoc_types.text -> Odoc_types.text * Odoc_types.text
+(** Return the given [text] without any title or list. *)
+val text_no_title_no_list : Odoc_types.text -> Odoc_types.text
+
(** Take a sorted list of elements, a function to get the name
of an element and return the list of list of elements,
where each list group elements beginning by the same letter.
diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml
index e7831b47f..5cc8c37fa 100644
--- a/ocamldoc/odoc_latex.ml
+++ b/ocamldoc/odoc_latex.ml
@@ -296,6 +296,9 @@ class latex =
(** Get the first sentence and the rest of a description,
from an optional [info] structure. The first sentence
can be empty if it would not appear right in a title.
+ In the first sentence, the titles and lists has been removed,
+ since it is used in LaTeX titles and would make LaTeX complain
+ if we has two nested \section commands.
*)
method first_and_rest_of_info i_opt =
match i_opt with
@@ -306,7 +309,7 @@ class latex =
| Some t ->
let (first,_) = Odoc_info.first_sentence_and_rest_of_text t in
let (_, rest) = Odoc_info.first_sentence_and_rest_of_text (self#text_of_info ~block: false i_opt) in
- (first, rest)
+ (Odoc_info.text_no_title_no_list first, rest)
(** Return LaTeX code for a value. *)
method latex_of_value v =
diff --git a/ocamldoc/odoc_misc.ml b/ocamldoc/odoc_misc.ml
index d6fee14e0..5f901f035 100644
--- a/ocamldoc/odoc_misc.ml
+++ b/ocamldoc/odoc_misc.ml
@@ -274,6 +274,43 @@ let string_of_date ?(hour=true) d =
)
+let rec text_list_concat sep l =
+ match l with
+ [] -> []
+ | [t] -> t
+ | t :: q ->
+ t @ (sep :: (text_list_concat sep q))
+
+let rec text_no_title_no_list t =
+ let rec iter t_ele =
+ match t_ele with
+ | Odoc_types.Title (_,_,t) -> text_no_title_no_list t
+ | Odoc_types.List l
+ | Odoc_types.Enum l ->
+ (Odoc_types.Raw " ") ::
+ (text_list_concat
+ (Odoc_types.Raw ", ")
+ (List.map text_no_title_no_list l))
+ | Odoc_types.Raw _
+ | Odoc_types.Code _
+ | Odoc_types.CodePre _
+ | Odoc_types.Verbatim _
+ | Odoc_types.Ref _ -> [t_ele]
+ | Odoc_types.Newline -> [Odoc_types.Newline]
+ | Odoc_types.Block t -> [Odoc_types.Block (text_no_title_no_list t)]
+ | Odoc_types.Bold t -> [Odoc_types.Bold (text_no_title_no_list t)]
+ | Odoc_types.Italic t -> [Odoc_types.Italic (text_no_title_no_list t)]
+ | Odoc_types.Center t -> [Odoc_types.Center (text_no_title_no_list t)]
+ | Odoc_types.Left t -> [Odoc_types.Left (text_no_title_no_list t)]
+ | Odoc_types.Right t -> [Odoc_types.Right (text_no_title_no_list t)]
+ | Odoc_types.Emphasize t -> [Odoc_types.Emphasize (text_no_title_no_list t)]
+ | Odoc_types.Latex s -> [Odoc_types.Latex s]
+ | Odoc_types.Link (s, t) -> [Odoc_types.Link (s, (text_no_title_no_list t))]
+ | Odoc_types.Superscript t -> [Odoc_types.Superscript (text_no_title_no_list t)]
+ | Odoc_types.Subscript t -> [Odoc_types.Subscript (text_no_title_no_list t)]
+ in
+ List.flatten (List.map iter t)
+
(*********************************************************)
let rec get_before_dot s =
diff --git a/ocamldoc/odoc_misc.mli b/ocamldoc/odoc_misc.mli
index 25c438966..beeb1b57b 100644
--- a/ocamldoc/odoc_misc.mli
+++ b/ocamldoc/odoc_misc.mli
@@ -88,6 +88,9 @@ val first_sentence_of_text : Odoc_types.text -> Odoc_types.text
val first_sentence_and_rest_of_text :
Odoc_types.text -> Odoc_types.text * Odoc_types.text
+(** Return the given [text] without any title or list. *)
+val text_no_title_no_list : Odoc_types.text -> Odoc_types.text
+
(** Take a sorted list of elements, a function to get the name
of an element and return the list of list of elements,
where each list group elements beginning by the same letter.