summaryrefslogtreecommitdiffstats
path: root/ocamldoc/odoc_misc.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocamldoc/odoc_misc.ml')
-rw-r--r--ocamldoc/odoc_misc.ml64
1 files changed, 38 insertions, 26 deletions
diff --git a/ocamldoc/odoc_misc.ml b/ocamldoc/odoc_misc.ml
index d3d970490..34d390035 100644
--- a/ocamldoc/odoc_misc.ml
+++ b/ocamldoc/odoc_misc.ml
@@ -11,6 +11,16 @@
(* $Id$ *)
+let no_blanks s =
+ let len = String.length s in
+ let buf = Buffer.create len in
+ for i = 0 to len - 1 do
+ match s.[i] with
+ ' ' | '\n' | '\t' | '\r' -> ()
+ | c -> Buffer.add_char buf c
+ done;
+ Buffer.contents buf
+
let input_file_as_string nom =
let chanin = open_in_bin nom in
let len = 1024 in
@@ -38,15 +48,15 @@ let split_string s chars =
let rec iter acc pos =
if pos >= len then
match acc with
- "" -> []
- | _ -> [acc]
+ "" -> []
+ | _ -> [acc]
else
if List.mem s.[pos] chars then
- match acc with
- "" -> iter "" (pos + 1)
- | _ -> acc :: (iter "" (pos + 1))
+ match acc with
+ "" -> iter "" (pos + 1)
+ | _ -> acc :: (iter "" (pos + 1))
else
- iter (Printf.sprintf "%s%c" acc s.[pos]) (pos + 1)
+ iter (Printf.sprintf "%s%c" acc s.[pos]) (pos + 1)
in
iter "" 0
@@ -115,13 +125,14 @@ let rec string_of_text t =
"^{"^(string_of_text t)^"}"
| Odoc_types.Subscript t ->
"^{"^(string_of_text t)^"}"
- | Odoc_types.Module_list l ->
- string_of_text
- (list_concat (Odoc_types.Raw ", ")
- (List.map (fun s -> Odoc_types.Code s) l)
- )
- | Odoc_types.Index_list ->
- ""
+ | Odoc_types.Module_list l ->
+ string_of_text
+ (list_concat (Odoc_types.Raw ", ")
+ (List.map (fun s -> Odoc_types.Code s) l)
+ )
+ | Odoc_types.Index_list ->
+ ""
+ | Odoc_types.Custom (_, t) -> string_of_text t
in
String.concat "" (List.map iter t)
@@ -256,12 +267,13 @@ let rec 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)]
| Odoc_types.Module_list l ->
- list_concat (Odoc_types.Raw ", ")
- (List.map
- (fun s -> Odoc_types.Ref (s, Some Odoc_types.RK_module))
- l
- )
+ list_concat (Odoc_types.Raw ", ")
+ (List.map
+ (fun s -> Odoc_types.Ref (s, Some Odoc_types.RK_module))
+ l
+ )
| Odoc_types.Index_list -> []
+ | Odoc_types.Custom (s,t) -> [Odoc_types.Custom (s, text_no_title_no_list t)]
in
List.flatten (List.map iter t)
@@ -291,6 +303,7 @@ let get_titles_in_text t =
| Odoc_types.Subscript t -> iter_text t
| Odoc_types.Module_list _ -> ()
| Odoc_types.Index_list -> ()
+ | Odoc_types.Custom (_, t) -> iter_text t
and iter_text te =
List.iter iter_ele te
in
@@ -382,6 +395,7 @@ and first_sentence_text_ele text_ele =
| Odoc_types.Subscript _
| Odoc_types.Module_list _
| Odoc_types.Index_list -> (false, text_ele, None)
+ | Odoc_types.Custom _ -> (false, text_ele, None)
let first_sentence_of_text t =
let (_,t2,_) = first_sentence_text t in
@@ -408,12 +422,12 @@ let search_string_backward ~pat =
-1 -> raise Not_found
| 0 -> if pat = s then 0 else raise Not_found
| _ ->
- let pos = len - lenp in
- let s2 = String.sub s pos lenp in
- if s2 = pat then
- pos
- else
- iter (String.sub s 0 pos)
+ let pos = len - lenp in
+ let s2 = String.sub s pos lenp in
+ if s2 = pat then
+ pos
+ else
+ iter (String.sub s 0 pos)
in
fun ~s -> iter s
@@ -465,5 +479,3 @@ let remove_option typ =
| Types.Tsubst t2 -> iter t2.Types.desc
in
{ typ with Types.desc = iter typ.Types.desc }
-
-(* eof $Id$ *)