summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2003-12-21 11:56:56 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2003-12-21 11:56:56 +0000
commit5fbdbc16c69060b029dc2c8d7350a524bc4b733d (patch)
tree6ca3f11960a3410b47caee3afec460d119f87ca6
parent750ecaff2c070163bde6954539ce693e46717be8 (diff)
fix in info_string_of_info
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6035 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--ocamldoc/Changes.txt1
-rw-r--r--ocamldoc/odoc_info.ml90
-rw-r--r--ocamldoc/odoc_info.mli7
3 files changed, 97 insertions, 1 deletions
diff --git a/ocamldoc/Changes.txt b/ocamldoc/Changes.txt
index 3f432819a..f87bf23ef 100644
--- a/ocamldoc/Changes.txt
+++ b/ocamldoc/Changes.txt
@@ -1,4 +1,5 @@
Current :
+OK - fix: missing spaces after carriage return in types (Odoc_misc.string_of_type_expr)
OK - fixes: some bugs in the text parser
( ]} meaning end of code and somehting else instead of end of precode)
OK - add: in Odoc_info: text_of_string, text_string_of_text, info_of_string
diff --git a/ocamldoc/odoc_info.ml b/ocamldoc/odoc_info.ml
index 4e11dfe2e..ab5210db3 100644
--- a/ocamldoc/odoc_info.ml
+++ b/ocamldoc/odoc_info.ml
@@ -182,6 +182,96 @@ let text_of_string = Odoc_text.Texter.text_of_string
let text_string_of_text = Odoc_text.Texter.string_of_text
+
+let escape_arobas s =
+ let len = String.length s in
+ let b = Buffer.create len in
+ for i = 0 to len - 1 do
+ match s.[i] with
+ '@' -> Buffer.add_string b "\\@"
+ | c -> Buffer.add_char b c
+ done;
+ Buffer.contents b
+
+let info_string_of_info i =
+ let b = Buffer.create 256 in
+ let p = Printf.bprintf in
+ (
+ match i.i_desc with
+ None -> ()
+ | Some t -> p b "%s" (escape_arobas (text_string_of_text t))
+ );
+ List.iter
+ (fun s -> p b "\n@author %s" (escape_arobas s))
+ i.i_authors;
+ (
+ match i.i_version with
+ None -> ()
+ | Some s -> p b "\n@version %s" (escape_arobas s)
+ );
+ (
+ (* TODO: escape characters ? *)
+ let f_see_ref = function
+ See_url s -> Printf.sprintf "<%s>" s
+ | See_file s -> Printf.sprintf "'%s'" s
+ | See_doc s -> Printf.sprintf "\"%s\"" s
+ in
+ List.iter
+ (fun (sref, t) ->
+ p b "\n@see %s %s"
+ (escape_arobas (f_see_ref sref))
+ (escape_arobas (text_string_of_text t))
+ )
+ i.i_sees
+ );
+ (
+ match i.i_since with
+ None -> ()
+ | Some s -> p b "\n@since %s" (escape_arobas s)
+ );
+ (
+ match i.i_deprecated with
+ None -> ()
+ | Some t ->
+ p b "\n@deprecated %s"
+ (escape_arobas (text_string_of_text t))
+ );
+ List.iter
+ (fun (s, t) ->
+ p b "\n@param %s %s"
+ (escape_arobas s)
+ (escape_arobas (text_string_of_text t))
+ )
+ i.i_params;
+ List.iter
+ (fun (s, t) ->
+ p b "\n@raise %s %s"
+ (escape_arobas s)
+ (escape_arobas (text_string_of_text t))
+ )
+ i.i_raised_exceptions;
+ (
+ match i.i_return_value with
+ None -> ()
+ | Some t ->
+ p b "\n@return %s"
+ (escape_arobas (text_string_of_text t))
+ );
+ List.iter
+ (fun (s, t) ->
+ p b "\n@%s %s" s
+ (escape_arobas (text_string_of_text t))
+ )
+ i.i_raised_exceptions;
+ List.iter
+ (fun (s, t) ->
+ p b "\n@%s %s" s
+ (escape_arobas (text_string_of_text t))
+ )
+ i.i_custom;
+
+ Buffer.contents b
+
let info_of_string s =
let dummy =
{
diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli
index e4b97cdb9..333f0221e 100644
--- a/ocamldoc/odoc_info.mli
+++ b/ocamldoc/odoc_info.mli
@@ -734,7 +734,7 @@ val apply_if_equal : ('a -> 'a) -> 'a -> 'a -> 'a
@raise Text_syntax if a syntax error is encountered. *)
val text_of_string : string -> text
-(** [string_text_of_text text] returns the string representing
+(** [text_string_of_text text] returns the string representing
the given [text]. This string can then be parsed again
by {!Odoc_info.text_of_string}.*)
val text_string_of_text : text -> string
@@ -746,6 +746,11 @@ val text_string_of_text : text -> string
*)
val info_of_string : string -> info
+(** [info_string_of_info info] returns the string representing
+ the given [info]. This string can then be parsed again
+ by {!Odoc_info.info_of_string}.*)
+val info_string_of_info : info -> string
+
(** [info_of_comment_file file] parses the given file
and return an {!Odoc_info.info} structure. The content of the
file must have the same syntax as the content of a special comment.