diff options
-rw-r--r-- | ocamldoc/generators/odoc_todo.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_analyse.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_dot.ml | 1 | ||||
-rw-r--r-- | ocamldoc/odoc_global.ml | 3 | ||||
-rw-r--r-- | ocamldoc/odoc_html.ml | 6 | ||||
-rw-r--r-- | ocamldoc/odoc_info.mli | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_latex.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_man.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_name.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_sig.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_texi.ml | 6 |
11 files changed, 16 insertions, 20 deletions
diff --git a/ocamldoc/generators/odoc_todo.ml b/ocamldoc/generators/odoc_todo.ml index 7c025e127..626236cf1 100644 --- a/ocamldoc/generators/odoc_todo.ml +++ b/ocamldoc/generators/odoc_todo.ml @@ -48,7 +48,7 @@ struct method private gen_if_tag name target info_opt = match info_opt with None -> () - | Some i -> + | Some i -> let l = List.fold_left (fun acc (t, text) -> @@ -69,7 +69,7 @@ struct | _ -> (None, text) :: acc end - | _ -> acc + | _ -> acc ) [] i.i_custom diff --git a/ocamldoc/odoc_analyse.ml b/ocamldoc/odoc_analyse.ml index cc0cf57b2..c07cf4c93 100644 --- a/ocamldoc/odoc_analyse.ml +++ b/ocamldoc/odoc_analyse.ml @@ -64,7 +64,7 @@ let process_implementation_file ppf sourcefile = let parsetree = Pparse.file Format.err_formatter inputfile Parse.implementation ast_impl_magic_number in let typedtree = Typemod.type_implementation - sourcefile prefixname modulename env parsetree + sourcefile prefixname modulename env parsetree in (Some (parsetree, typedtree), inputfile) with diff --git a/ocamldoc/odoc_dot.ml b/ocamldoc/odoc_dot.ml index a0d5ee222..bf35e8621 100644 --- a/ocamldoc/odoc_dot.ml +++ b/ocamldoc/odoc_dot.ml @@ -143,4 +143,3 @@ class dot = end module type Dot_generator = module type of Generator - diff --git a/ocamldoc/odoc_global.ml b/ocamldoc/odoc_global.ml index dc9635118..24f0ac290 100644 --- a/ocamldoc/odoc_global.ml +++ b/ocamldoc/odoc_global.ml @@ -85,6 +85,3 @@ let with_trailer = ref true let with_toc = ref true let with_index = ref true - - - diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml index e3ce5344a..85b052e30 100644 --- a/ocamldoc/odoc_html.ml +++ b/ocamldoc/odoc_html.ml @@ -836,9 +836,9 @@ class html = "pre.verbatim, pre.codepre { }"; ".indextable {border: 1px #ddd solid; border-collapse: collapse}"; - ".indextable td, .indextable th {border: 1px #ddd solid; min-width: 80px}"; + ".indextable td, .indextable th {border: 1px #ddd solid; min-width: 80px}"; ".indextable td.module {background-color: #eee ; padding-left: 2px; padding-right: 2px}"; - ".indextable td.module a {color: 4E6272; text-decoration: none; display: block; width: 100%}"; + ".indextable td.module a {color: 4E6272; text-decoration: none; display: block; width: 100%}"; ".indextable td.module a:hover {text-decoration: underline; background-color: transparent}"; ".deprecated {color: #888; font-style: italic}" ; @@ -1513,7 +1513,7 @@ class html = | l,Some r -> bs b (" " ^ (self#keyword ":") ^ " "); self#html_of_type_expr_list ~par: false b father " * " l; - bs b (" " ^ (self#keyword "->") ^ " "); + bs b (" " ^ (self#keyword "->") ^ " "); self#html_of_type_expr b father r; ); bs b "</code></td>\n"; diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli index 0d755c7f4..15332fd53 100644 --- a/ocamldoc/odoc_info.mli +++ b/ocamldoc/odoc_info.mli @@ -203,7 +203,7 @@ module Type : { vc_name : string ; (** Name of the constructor. *) vc_args : Types.type_expr list ; (** Arguments of the constructor. *) - vc_ret : Types.type_expr option ; + vc_ret : Types.type_expr option ; mutable vc_text : text option ; (** Optional description in the associated comment. *) } diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml index 83844e0f5..901be36c1 100644 --- a/ocamldoc/odoc_latex.ml +++ b/ocamldoc/odoc_latex.ml @@ -574,7 +574,7 @@ class latex = p fmt2 " %s@ %s@ %s@ %s" ":" (self#normal_type_list ~par: false mod_name " * " l) - "->" + "->" (self#normal_type mod_name r) ); flush2 () diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml index dae2ff986..e6a3ed3d1 100644 --- a/ocamldoc/odoc_man.ml +++ b/ocamldoc/odoc_man.ml @@ -492,13 +492,13 @@ class man = | l, None, Some r -> bs b "\n.B : "; self#man_of_type_expr_list ~par: false b father " * " l; - bs b ".B -> "; + bs b ".B -> "; self#man_of_type_expr b father r; bs b " " | l, (Some t), Some r -> bs b "\n.B of "; self#man_of_type_expr_list ~par: false b father " * " l; - bs b ".B -> "; + bs b ".B -> "; self#man_of_type_expr b father r; bs b ".I \" \"\n"; bs b "(* "; diff --git a/ocamldoc/odoc_name.ml b/ocamldoc/odoc_name.ml index 7d059df40..9a934d752 100644 --- a/ocamldoc/odoc_name.ml +++ b/ocamldoc/odoc_name.ml @@ -52,11 +52,11 @@ let strip_string s = else match s.[n] with ' ' | '\t' | '\n' | '\r' -> iter_last (n-1) - | _ -> Some n + | _ -> Some n in match iter_last (len-1) with None -> String.sub s first 1 - | Some last -> String.sub s first ((last-first)+1) + | Some last -> String.sub s first ((last-first)+1) let parens_if_infix name = match strip_string name with diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml index f4e9ba50d..de0c6718e 100644 --- a/ocamldoc/odoc_sig.ml +++ b/ocamldoc/odoc_sig.ml @@ -232,7 +232,7 @@ module Analyser = { vc_name = constructor_name ; vc_args = List.map (Odoc_env.subst_type env) type_expr_list ; - vc_ret = may_map (Odoc_env.subst_type env) ret_type; + vc_ret = may_map (Odoc_env.subst_type env) ret_type; vc_text = comment_opt } in diff --git a/ocamldoc/odoc_texi.ml b/ocamldoc/odoc_texi.ml index b862960b6..eeb4d9e23 100644 --- a/ocamldoc/odoc_texi.ml +++ b/ocamldoc/odoc_texi.ml @@ -640,13 +640,13 @@ class texi = Printf.sprintf "(%s) " (String.concat ", " (List.map f l)) - method string_of_type_args (args:Types.type_expr list) (ret:Types.type_expr option) = + method string_of_type_args (args:Types.type_expr list) (ret:Types.type_expr option) = match args, ret with | [], None -> "" | args, None -> " of " ^ (Odoc_info.string_of_type_list " * " args) | [], Some r -> " : " ^ (Odoc_info.string_of_type_expr r) - | args, Some r -> " : " ^ (Odoc_info.string_of_type_list " * " args) ^ - " -> " ^ (Odoc_info.string_of_type_expr r) + | args, Some r -> " : " ^ (Odoc_info.string_of_type_list " * " args) ^ + " -> " ^ (Odoc_info.string_of_type_expr r) (** Return Texinfo code for a type. *) method texi_of_type ty = |