summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--ocamldoc/.depend12
-rw-r--r--ocamldoc/odoc_comments.ml5
-rw-r--r--ocamldoc/odoc_comments_global.ml3
-rw-r--r--ocamldoc/odoc_comments_global.mli3
-rw-r--r--ocamldoc/odoc_html.ml10
-rw-r--r--ocamldoc/odoc_info.ml1
-rw-r--r--ocamldoc/odoc_info.mli5
-rw-r--r--ocamldoc/odoc_lexer.mll2
-rw-r--r--ocamldoc/odoc_man.ml17
-rw-r--r--ocamldoc/odoc_merge.ml22
-rw-r--r--ocamldoc/odoc_merge.mli4
-rw-r--r--ocamldoc/odoc_messages.ml1
-rw-r--r--ocamldoc/odoc_parser.mly18
-rw-r--r--ocamldoc/odoc_texi.ml6
-rw-r--r--ocamldoc/odoc_to_text.ml12
-rw-r--r--ocamldoc/odoc_types.ml2
-rw-r--r--ocamldoc/odoc_types.mli1
17 files changed, 119 insertions, 5 deletions
diff --git a/ocamldoc/.depend b/ocamldoc/.depend
index 851a3be00..c05f40336 100644
--- a/ocamldoc/.depend
+++ b/ocamldoc/.depend
@@ -55,11 +55,13 @@ odoc_class.cmo: ../typing/types.cmi odoc_value.cmo odoc_types.cmi \
odoc_class.cmx: ../typing/types.cmx odoc_value.cmx odoc_types.cmx \
odoc_parameter.cmx odoc_name.cmx
odoc_comments.cmo: odoc_types.cmi odoc_text.cmi odoc_see_lexer.cmo \
- odoc_parser.cmi odoc_misc.cmi odoc_messages.cmo odoc_lexer.cmo \
- odoc_global.cmi odoc_cross.cmi odoc_comments_global.cmi odoc_comments.cmi
+ odoc_parser.cmi odoc_misc.cmi odoc_messages.cmo odoc_merge.cmi \
+ odoc_lexer.cmo odoc_global.cmi odoc_cross.cmi odoc_comments_global.cmi \
+ odoc_comments.cmi
odoc_comments.cmx: odoc_types.cmx odoc_text.cmx odoc_see_lexer.cmx \
- odoc_parser.cmx odoc_misc.cmx odoc_messages.cmx odoc_lexer.cmx \
- odoc_global.cmx odoc_cross.cmx odoc_comments_global.cmx odoc_comments.cmi
+ odoc_parser.cmx odoc_misc.cmx odoc_messages.cmx odoc_merge.cmx \
+ odoc_lexer.cmx odoc_global.cmx odoc_cross.cmx odoc_comments_global.cmx \
+ odoc_comments.cmi
odoc_comments_global.cmo: odoc_comments_global.cmi
odoc_comments_global.cmx: odoc_comments_global.cmi
odoc_config.cmo: ../utils/config.cmi odoc_config.cmi
@@ -212,6 +214,8 @@ odoc_value.cmo: ../typing/types.cmi ../typing/printtyp.cmi odoc_types.cmi \
odoc_parameter.cmo odoc_name.cmi
odoc_value.cmx: ../typing/types.cmx ../typing/printtyp.cmx odoc_types.cmx \
odoc_parameter.cmx odoc_name.cmx
+t.cmo:
+t.cmx:
odoc_analyse.cmi: odoc_module.cmo odoc_args.cmi
odoc_args.cmi: odoc_types.cmi odoc_module.cmo
odoc_ast.cmi: ../typing/types.cmi ../typing/typedtree.cmi ../typing/path.cmi \
diff --git a/ocamldoc/odoc_comments.ml b/ocamldoc/odoc_comments.ml
index 51873e305..ea5427e07 100644
--- a/ocamldoc/odoc_comments.ml
+++ b/ocamldoc/odoc_comments.ml
@@ -67,6 +67,10 @@ module Info_retriever =
i_version = !Odoc_comments_global.version;
i_sees = (List.map create_see !Odoc_comments_global.sees) ;
i_since = !Odoc_comments_global.since;
+ i_before = Odoc_merge.merge_before_tags
+ (List.map (fun (n, s) ->
+ (n, MyTexter.text_of_string s)) !Odoc_comments_global.before)
+ ;
i_deprecated =
(match !Odoc_comments_global.deprecated with
None -> None | Some s -> Some (MyTexter.text_of_string s));
@@ -320,6 +324,7 @@ let info_of_string s =
i_version = None ;
i_sees = [] ;
i_since = None ;
+ i_before = [] ;
i_deprecated = None ;
i_params = [] ;
i_raised_exceptions = [] ;
diff --git a/ocamldoc/odoc_comments_global.ml b/ocamldoc/odoc_comments_global.ml
index 86663d58c..a4366ceb7 100644
--- a/ocamldoc/odoc_comments_global.ml
+++ b/ocamldoc/odoc_comments_global.ml
@@ -23,6 +23,8 @@ let sees = ref ([] : string list)
let since = ref (None : string option)
+let before = ref []
+
let deprecated = ref (None : string option)
let params = ref ([] : (string * string) list)
@@ -39,6 +41,7 @@ let init () =
version := None;
sees := [];
since := None;
+ before := [];
deprecated := None;
params := [];
raised_exceptions := [];
diff --git a/ocamldoc/odoc_comments_global.mli b/ocamldoc/odoc_comments_global.mli
index 9e0474676..e9efbffc5 100644
--- a/ocamldoc/odoc_comments_global.mli
+++ b/ocamldoc/odoc_comments_global.mli
@@ -28,6 +28,9 @@ val sees : string list ref
(** the since string *)
val since : string option ref
+(** the before tag information *)
+val before : (string * string) list ref
+
(** the deprecated flag *)
val deprecated : string option ref
diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml
index 7cfb9890c..7b9050fb0 100644
--- a/ocamldoc/odoc_html.ml
+++ b/ocamldoc/odoc_html.ml
@@ -550,6 +550,15 @@ class virtual info =
| Some s ->
bp b "<b>%s</b> %s<br>\n" Odoc_messages.since s
+ (** Print html code for the given "before" information.*)
+ method html_of_before b l =
+ let f (v, text) =
+ bp b "<b>%s %s </b> " Odoc_messages.before v;
+ self#html_of_text b text;
+ bs b "<br>\n"
+ in
+ List.iter f l
+
(** Print html code for the given list of raised exceptions.*)
method html_of_raised_exceptions b l =
match l with
@@ -651,6 +660,7 @@ class virtual info =
);
self#html_of_author_list b info.M.i_authors;
self#html_of_version_opt b info.M.i_version;
+ self#html_of_before b info.M.i_before;
self#html_of_since_opt b info.M.i_since;
self#html_of_raised_exceptions b info.M.i_raised_exceptions;
self#html_of_return_opt b info.M.i_return_value;
diff --git a/ocamldoc/odoc_info.ml b/ocamldoc/odoc_info.ml
index 4eca5fd2f..fa3c585ed 100644
--- a/ocamldoc/odoc_info.ml
+++ b/ocamldoc/odoc_info.ml
@@ -72,6 +72,7 @@ type info = Odoc_types.info = {
i_version : string option;
i_sees : see list;
i_since : string option;
+ i_before : (string * text) list ;
i_deprecated : text option;
i_params : param list;
i_raised_exceptions : raised_exception list;
diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli
index 04971c4e6..7c6dc4912 100644
--- a/ocamldoc/odoc_info.mli
+++ b/ocamldoc/odoc_info.mli
@@ -79,13 +79,16 @@ type param = (string * text)
(** Raised exception name and description. *)
type raised_exception = (string * text)
-(** Information in a special comment *)
+(** Information in a special comment
+@before 3.12.0 \@before information was not present.
+*)
type info = Odoc_types.info = {
i_desc : text option; (** The description text. *)
i_authors : string list; (** The list of authors in \@author tags. *)
i_version : string option; (** The string in the \@version tag. *)
i_sees : see list; (** The list of \@see tags. *)
i_since : string option; (** The string in the \@since tag. *)
+ i_before : (string * text) list ; (** the version number and text in \@before tag *)
i_deprecated : text option; (** The of the \@deprecated tag. *)
i_params : param list; (** The list of parameter descriptions. *)
i_raised_exceptions : raised_exception list; (** The list of raised exceptions. *)
diff --git a/ocamldoc/odoc_lexer.mll b/ocamldoc/odoc_lexer.mll
index da66a0087..7b34b3642 100644
--- a/ocamldoc/odoc_lexer.mll
+++ b/ocamldoc/odoc_lexer.mll
@@ -313,6 +313,8 @@ and elements = parse
T_SEE
| "since" ->
T_SINCE
+ | "before" ->
+ T_BEFORE
| "deprecated" ->
T_DEPRECATED
| "raise" ->
diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml
index 44d503f22..eb6ec4d7d 100644
--- a/ocamldoc/odoc_man.ml
+++ b/ocamldoc/odoc_man.ml
@@ -58,6 +58,22 @@ class virtual info =
bs b v;
bs b "\n.sp\n"
+ (** Printf groff string for the \@before information. *)
+ method man_of_before b = function
+ [] -> ()
+ | l ->
+ List.iter
+ (fun (v, text) ->
+ bp b ".B \"%s" Odoc_messages.before;
+ bs b v;
+ bs b "\"\n";
+ self#man_of_text b text;
+ bs b "\n";
+ bs b "\n.sp\n"
+ )
+ l
+
+
(** Print groff string for the given optional since information.*)
method man_of_since_opt b s_opt =
match s_opt with
@@ -178,6 +194,7 @@ class virtual info =
);
self#man_of_author_list b info.M.i_authors;
self#man_of_version_opt b info.M.i_version;
+ self#man_of_before b info.M.i_before;
self#man_of_since_opt b info.M.i_since;
self#man_of_raised_exceptions b info.M.i_raised_exceptions;
self#man_of_return_opt b info.M.i_return_value;
diff --git a/ocamldoc/odoc_merge.ml b/ocamldoc/odoc_merge.ml
index fd046752e..44804ba0b 100644
--- a/ocamldoc/odoc_merge.ml
+++ b/ocamldoc/odoc_merge.ml
@@ -23,6 +23,26 @@ open Odoc_exception
open Odoc_class
open Odoc_module
+let merge_before_tags l =
+ let rec iter acc = function
+ [] -> List.rev acc
+ | (v, text) :: q ->
+ let (l1, l2) = List.partition
+ (fun (v2,_) -> v = v2) q
+ in
+ let acc =
+ let text =
+ List.fold_left
+ (fun acc t -> acc @ [Raw " "] @ t)
+ text (List.map snd l1)
+ in
+ (v, text) :: acc
+ in
+ iter acc l2
+ in
+ iter [] l
+;;
+
(** Merge two Odoctypes.info struture, completing the information of
the first one with the information in the second one.
The merge treatment depends on a given merge_option list.
@@ -83,6 +103,7 @@ let merge_info merge_options (m1 : info) (m2 : info) =
else
Some v1
in
+ let new_before = merge_before_tags (m1.i_before @ m2.i_before) in
let new_dep =
match m1.i_deprecated, m2.i_deprecated with
None, None -> None
@@ -170,6 +191,7 @@ let merge_info merge_options (m1 : info) (m2 : info) =
Odoc_types.i_version = new_version ;
Odoc_types.i_sees = new_sees ;
Odoc_types.i_since = new_since ;
+ Odoc_types.i_before = new_before ;
Odoc_types.i_deprecated = new_dep ;
Odoc_types.i_params = new_params ;
Odoc_types.i_raised_exceptions = new_raised_exceptions ;
diff --git a/ocamldoc/odoc_merge.mli b/ocamldoc/odoc_merge.mli
index 52d39033d..4f580ee89 100644
--- a/ocamldoc/odoc_merge.mli
+++ b/ocamldoc/odoc_merge.mli
@@ -13,6 +13,10 @@
(** Merge of information from [.ml] and [.mli] for a module.*)
+(** Merging \@before tags. *)
+val merge_before_tags :
+ (string * Odoc_types.text) list -> (string * Odoc_types.text) list
+
(** Merge of two optional info structures.
Used to merge a comment before and a comment after
an element in [Odoc_sig.Analyser.analyse_signature_item_desc]. *)
diff --git a/ocamldoc/odoc_messages.ml b/ocamldoc/odoc_messages.ml
index 078f2d649..a55d022f4 100644
--- a/ocamldoc/odoc_messages.ml
+++ b/ocamldoc/odoc_messages.ml
@@ -328,6 +328,7 @@ let methods = "Methods"
let authors = "Author(s)"
let version = "Version"
let since = "Since"
+let before = "Before"
let deprecated = "Deprecated."
let raises = "Raises"
let returns = "Returns"
diff --git a/ocamldoc/odoc_parser.mly b/ocamldoc/odoc_parser.mly
index 0d9d814d2..e62dcc551 100644
--- a/ocamldoc/odoc_parser.mly
+++ b/ocamldoc/odoc_parser.mly
@@ -34,6 +34,7 @@ let print_DEBUG s = print_string s; print_newline ()
%token T_VERSION
%token T_SEE
%token T_SINCE
+%token T_BEFORE
%token T_DEPRECATED
%token T_RAISES
%token T_RETURN
@@ -81,6 +82,7 @@ element:
| version { () }
| see { () }
| since { () }
+| before { () }
| deprecated { () }
| raise_exc { () }
| return { () }
@@ -122,6 +124,22 @@ see:
since:
T_SINCE Desc { since := Some $2 }
;
+before:
+ T_BEFORE Desc
+ {
+ (* isolate the version name *)
+ let s = $2 in
+ match Str.split (Str.regexp (blank^"+")) s with
+ []
+ | _ :: [] ->
+ raise (Failure "usage: @before version description")
+ | id :: _ ->
+ print_DEBUG ("version "^id);
+ let remain = String.sub s (String.length id) ((String.length s) - (String.length id)) in
+ let remain2 = Str.replace_first (Str.regexp ("^"^blank^"+")) "" remain in
+ before := !before @ [(id, remain2)]
+ }
+;
deprecated:
T_DEPRECATED Desc { deprecated := Some $2 }
;
diff --git a/ocamldoc/odoc_texi.ml b/ocamldoc/odoc_texi.ml
index 389462338..a853c4f7a 100644
--- a/ocamldoc/odoc_texi.ml
+++ b/ocamldoc/odoc_texi.ml
@@ -465,6 +465,11 @@ class texi =
Raw " " ; Raw s ] @ t @ [ Newline ])
see_l)
+ method text_of_before l =
+ List.flatten
+ (List.map
+ (fun x -> linebreak :: (to_text#text_of_before [x])) l)
+
method text_of_params params_list =
List.concat
(List.map
@@ -530,6 +535,7 @@ class texi =
self#text_of_version_opt info.i_version )
else [] ;
self#text_of_sees_opt info.i_sees ;
+ self#text_of_before info.i_before ;
if is info.i_since
then ( linebreak ::
self#text_of_since_opt info.i_since )
diff --git a/ocamldoc/odoc_to_text.ml b/ocamldoc/odoc_to_text.ml
index a3db5bd9b..591f81d61 100644
--- a/ocamldoc/odoc_to_text.ml
+++ b/ocamldoc/odoc_to_text.ml
@@ -61,6 +61,17 @@ class virtual info =
Newline
]
+ (** @return [text] value to represent the list of "before" information. *)
+ method text_of_before = function
+ [] -> []
+ | l ->
+ let f (v, text) =
+ (Bold [Raw (Printf.sprintf "%s %s " Odoc_messages.before v) ]) ::
+ text @
+ [Newline]
+ in
+ List.flatten (List.map f l)
+
(** @return [text] value for the given list of raised exceptions.*)
method text_of_raised_exceptions l =
match l with
@@ -153,6 +164,7 @@ class virtual info =
) @
(self#text_of_author_list info.i_authors) @
(self#text_of_version_opt info.i_version) @
+ (self#text_of_before info.i_before) @
(self#text_of_since_opt info.i_since) @
(self#text_of_raised_exceptions info.i_raised_exceptions) @
(self#text_of_return_opt info.i_return_value) @
diff --git a/ocamldoc/odoc_types.ml b/ocamldoc/odoc_types.ml
index db2778e0b..5c58afe16 100644
--- a/ocamldoc/odoc_types.ml
+++ b/ocamldoc/odoc_types.ml
@@ -68,6 +68,7 @@ type info = {
i_version : string option;
i_sees : see list;
i_since : string option;
+ i_before : (string * text) list;
i_deprecated : text option;
i_params : param list;
i_raised_exceptions : raised_exception list;
@@ -81,6 +82,7 @@ let dummy_info = {
i_version = None ;
i_sees = [] ;
i_since = None ;
+ i_before = [] ;
i_deprecated = None ;
i_params = [] ;
i_raised_exceptions = [] ;
diff --git a/ocamldoc/odoc_types.mli b/ocamldoc/odoc_types.mli
index 7050d42e3..639697f59 100644
--- a/ocamldoc/odoc_types.mli
+++ b/ocamldoc/odoc_types.mli
@@ -81,6 +81,7 @@ type info = {
i_version : string option; (** The string in the \@version tag. *)
i_sees : see list; (** The list of \@see tags. *)
i_since : string option; (** The string in the \@since tag. *)
+ i_before : (string * text) list; (** the version number and text in \@before tag *)
i_deprecated : text option; (** The of the \@deprecated tag. *)
i_params : param list; (** The list of parameter descriptions. *)
i_raised_exceptions : raised_exception list; (** The list of raised exceptions. *)