diff options
Diffstat (limited to 'ocamldoc')
-rw-r--r-- | ocamldoc/Changes.txt | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_cross.ml | 179 | ||||
-rw-r--r-- | ocamldoc/odoc_html.ml | 209 | ||||
-rw-r--r-- | ocamldoc/odoc_info.ml | 3 | ||||
-rw-r--r-- | ocamldoc/odoc_info.mli | 3 | ||||
-rw-r--r-- | ocamldoc/odoc_latex.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_man.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_misc.ml | 48 | ||||
-rw-r--r-- | ocamldoc/odoc_misc.mli | 3 | ||||
-rw-r--r-- | ocamldoc/odoc_search.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_texi.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_text.ml | 6 | ||||
-rw-r--r-- | ocamldoc/odoc_text_lexer.mll | 32 | ||||
-rw-r--r-- | ocamldoc/odoc_text_parser.mly | 10 | ||||
-rw-r--r-- | ocamldoc/odoc_types.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_types.mli | 3 |
16 files changed, 343 insertions, 171 deletions
diff --git a/ocamldoc/Changes.txt b/ocamldoc/Changes.txt index fcfb180b5..a832de16f 100644 --- a/ocamldoc/Changes.txt +++ b/ocamldoc/Changes.txt @@ -1,4 +1,6 @@ Current : +OK - parse des {!modules: } et {!indexlist} +OK - gestion des Module_list et Index_list OK - no need to Dynlink.add_available_units any more OK - generate html from module_kind rather than from module_type OK + same for classes and class types @@ -55,6 +57,8 @@ TODO: - latex: style latex pour indenter dans les module kind et les class kind OK - latex: il manque la génération des paramètres de classe - latex: types variant polymorphes dépassent de la page quand ils sont trop longs + - ajout à la doc de Module_list et Index_list (utilisé dans le html seulement) + - ajout ds la doc: fichier de l'option -intro utilisé pour l'index en html ====== diff --git a/ocamldoc/odoc_cross.ml b/ocamldoc/odoc_cross.ml index 5059b586e..cbe949ede 100644 --- a/ocamldoc/odoc_cross.ml +++ b/ocamldoc/odoc_cross.ml @@ -578,30 +578,69 @@ let ao = Odoc_misc.apply_opt let rec assoc_comments_text_elements module_list t_ele = match t_ele with - | Raw _ - | Code _ - | CodePre _ - | Latex _ - | Verbatim _ -> t_ele - | Bold t -> Bold (assoc_comments_text module_list t) - | Italic t -> Italic (assoc_comments_text module_list t) - | Center t -> Center (assoc_comments_text module_list t) - | Left t -> Left (assoc_comments_text module_list t) - | Right t -> Right (assoc_comments_text module_list t) - | Emphasize t -> Emphasize (assoc_comments_text module_list t) - | List l -> List (List.map (assoc_comments_text module_list) l) - | Enum l -> Enum (List.map (assoc_comments_text module_list) l) - | Newline -> Newline - | Block t -> Block (assoc_comments_text module_list t) - | Superscript t -> Superscript (assoc_comments_text module_list t) - | Subscript t -> Subscript (assoc_comments_text module_list t) - | Title (n, l_opt, t) -> Title (n, l_opt, (assoc_comments_text module_list t)) - | Link (s, t) -> Link (s, (assoc_comments_text module_list t)) - | Ref (name, None) -> - ( - match get_known_elements name with - [] -> + | Raw _ + | Code _ + | CodePre _ + | Latex _ + | Verbatim _ -> t_ele + | Bold t -> Bold (assoc_comments_text module_list t) + | Italic t -> Italic (assoc_comments_text module_list t) + | Center t -> Center (assoc_comments_text module_list t) + | Left t -> Left (assoc_comments_text module_list t) + | Right t -> Right (assoc_comments_text module_list t) + | Emphasize t -> Emphasize (assoc_comments_text module_list t) + | List l -> List (List.map (assoc_comments_text module_list) l) + | Enum l -> Enum (List.map (assoc_comments_text module_list) l) + | Newline -> Newline + | Block t -> Block (assoc_comments_text module_list t) + | Superscript t -> Superscript (assoc_comments_text module_list t) + | Subscript t -> Subscript (assoc_comments_text module_list t) + | Title (n, l_opt, t) -> Title (n, l_opt, (assoc_comments_text module_list t)) + | Link (s, t) -> Link (s, (assoc_comments_text module_list t)) + | Ref (name, None) -> + ( + match get_known_elements name with + [] -> + ( + try + let re = Str.regexp ("^"^(Str.quote name)^"$") in + let t = Odoc_search.find_section module_list re in + let v2 = (name, Some (RK_section t)) in + add_verified v2 ; + Ref (name, Some (RK_section t)) + with + Not_found -> + Odoc_messages.pwarning (Odoc_messages.cross_element_not_found name); + Ref (name, None) + ) + | ele :: _ -> + (* we look for the first element with this name *) + let kind = + match ele with + Odoc_search.Res_module _ -> RK_module + | Odoc_search.Res_module_type _ -> RK_module_type + | Odoc_search.Res_class _ -> RK_class + | Odoc_search.Res_class_type _ -> RK_class_type + | Odoc_search.Res_value _ -> RK_value + | Odoc_search.Res_type _ -> RK_type + | Odoc_search.Res_exception _ -> RK_exception + | Odoc_search.Res_attribute _ -> RK_attribute + | Odoc_search.Res_method _ -> RK_method + | Odoc_search.Res_section (_ ,t)-> assert false + in + add_verified (name, Some kind) ; + Ref (name, Some kind) + ) + | Ref (name, Some kind) -> + ( + let v = (name, Some kind) in + if was_verified v then + Ref (name, Some kind) + else + match kind with + | RK_section _ -> ( + (** we just verify that we find an element of this kind with this name *) try let re = Str.regexp ("^"^(Str.quote name)^"$") in let t = Odoc_search.find_section module_list re in @@ -610,72 +649,38 @@ let rec assoc_comments_text_elements module_list t_ele = Ref (name, Some (RK_section t)) with Not_found -> - Odoc_messages.pwarning (Odoc_messages.cross_element_not_found name); + Odoc_messages.pwarning (Odoc_messages.cross_section_not_found name); Ref (name, None) ) - | ele :: _ -> - (* we look for the first element with this name *) - let kind = - match ele with - Odoc_search.Res_module _ -> RK_module - | Odoc_search.Res_module_type _ -> RK_module_type - | Odoc_search.Res_class _ -> RK_class - | Odoc_search.Res_class_type _ -> RK_class_type - | Odoc_search.Res_value _ -> RK_value - | Odoc_search.Res_type _ -> RK_type - | Odoc_search.Res_exception _ -> RK_exception - | Odoc_search.Res_attribute _ -> RK_attribute - | Odoc_search.Res_method _ -> RK_method - | Odoc_search.Res_section (_ ,t)-> assert false - in - add_verified (name, Some kind) ; - Ref (name, Some kind) - ) - | Ref (name, Some kind) -> - let v = (name, Some kind) in - if was_verified v then - Ref (name, Some kind) - else - match kind with - | RK_section _ -> - ( - (** we just verify that we find an element of this kind with this name *) - try - let re = Str.regexp ("^"^(Str.quote name)^"$") in - let t = Odoc_search.find_section module_list re in - let v2 = (name, Some (RK_section t)) in - add_verified v2 ; - Ref (name, Some (RK_section t)) - with - Not_found -> - Odoc_messages.pwarning (Odoc_messages.cross_section_not_found name); - Ref (name, None) - ) - | _ -> - let (f,f_mes) = - match kind with - RK_module -> module_exists, Odoc_messages.cross_module_not_found - | RK_module_type -> module_type_exists, Odoc_messages.cross_module_type_not_found - | RK_class -> class_exists, Odoc_messages.cross_class_not_found - | RK_class_type -> class_type_exists, Odoc_messages.cross_class_type_not_found - | RK_value -> value_exists, Odoc_messages.cross_value_not_found - | RK_type -> type_exists, Odoc_messages.cross_type_not_found - | RK_exception -> exception_exists, Odoc_messages.cross_exception_not_found - | RK_attribute -> attribute_exists, Odoc_messages.cross_attribute_not_found - | RK_method -> method_exists, Odoc_messages.cross_method_not_found - | RK_section _ -> assert false - in - if f name then - ( - add_verified v ; - Ref (name, Some kind) - ) - else - ( - Odoc_messages.pwarning (f_mes name); - Ref (name, None) - ) - + | _ -> + let (f,f_mes) = + match kind with + RK_module -> module_exists, Odoc_messages.cross_module_not_found + | RK_module_type -> module_type_exists, Odoc_messages.cross_module_type_not_found + | RK_class -> class_exists, Odoc_messages.cross_class_not_found + | RK_class_type -> class_type_exists, Odoc_messages.cross_class_type_not_found + | RK_value -> value_exists, Odoc_messages.cross_value_not_found + | RK_type -> type_exists, Odoc_messages.cross_type_not_found + | RK_exception -> exception_exists, Odoc_messages.cross_exception_not_found + | RK_attribute -> attribute_exists, Odoc_messages.cross_attribute_not_found + | RK_method -> method_exists, Odoc_messages.cross_method_not_found + | RK_section _ -> assert false + in + if f name then + ( + add_verified v ; + Ref (name, Some kind) + ) + else + ( + Odoc_messages.pwarning (f_mes name); + Ref (name, None) + ) + ) + | Module_list l -> + Module_list l + | Index_list -> + Index_list and assoc_comments_text module_list text = List.map (assoc_comments_text_elements module_list) text diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml index 0e6c29b21..cbba5228f 100644 --- a/ocamldoc/odoc_html.ml +++ b/ocamldoc/odoc_html.ml @@ -184,7 +184,7 @@ let bs = Buffer.add_string (** Generation of html code from text structures. *) -class text = +class virtual text = object (self) (** We want to display colorized code. *) inherit ocaml_code @@ -246,6 +246,8 @@ class text = | Odoc_info.Ref (name, ref_opt) -> self#html_of_Ref b name ref_opt | Odoc_info.Superscript t -> self#html_of_Superscript b t | Odoc_info.Subscript t -> self#html_of_Subscript b t + | Odoc_info.Module_list l -> self#html_of_Module_list b l + | Odoc_info.Index_list -> self#html_of_Index_list b method html_of_Raw b s = bs b (self#escape s) @@ -398,6 +400,65 @@ class text = self#html_of_text b t; bs b "</sub>" + method html_of_Module_list b l = + bs b "<br>\n<table class=\"indextable\">\n"; + List.iter + (fun name -> + bs b "<tr><td>"; + ( + try + let m = + List.find (fun m -> m.m_name = name) self#list_modules + in + let (html, _) = Naming.html_files m.m_name in + bp b "<a href=\"%s\">%s</a></td>" html m.m_name; + bs b "<td>"; + self#html_of_info_first_sentence b m.m_info; + with + Not_found -> + Odoc_messages.pwarning (Odoc_messages.cross_module_not_found name); + bp b "%s</td><td>" name + ); + bs b "</td></tr>\n" + ) + l; + bs b "</table>\n</body>\n</html>"; + + method html_of_Index_list b = + let index_if_not_empty l url m = + match l with + [] -> () + | _ -> bp b "<a href=\"%s\">%s</a><br>\n" url m + in + index_if_not_empty self#list_types self#index_types Odoc_messages.index_of_types; + index_if_not_empty self#list_exceptions self#index_exceptions Odoc_messages.index_of_exceptions; + index_if_not_empty self#list_values self#index_values Odoc_messages.index_of_values; + index_if_not_empty self#list_attributes self#index_attributes Odoc_messages.index_of_attributes; + index_if_not_empty self#list_methods self#index_methods Odoc_messages.index_of_methods; + index_if_not_empty self#list_classes self#index_classes Odoc_messages.index_of_classes; + index_if_not_empty self#list_class_types self#index_class_types Odoc_messages.index_of_class_types; + index_if_not_empty self#list_modules self#index_modules Odoc_messages.index_of_modules; + index_if_not_empty self#list_module_types self#index_module_types Odoc_messages.index_of_module_types + + method virtual list_types : Odoc_info.Type.t_type list + method virtual index_types : string + method virtual list_exceptions : Odoc_info.Exception.t_exception list + method virtual index_exceptions : string + method virtual list_values : Odoc_info.Value.t_value list + method virtual index_values : string + method virtual list_attributes : Odoc_info.Value.t_attribute list + method virtual index_attributes : string + method virtual list_methods : Odoc_info.Value.t_method list + method virtual index_methods : string + method virtual list_classes : Odoc_info.Class.t_class list + method virtual index_classes : string + method virtual list_class_types : Odoc_info.Class.t_class_type list + method virtual index_class_types : string + method virtual list_modules : Odoc_info.Module.t_module list + method virtual index_modules : string + method virtual list_module_types : Odoc_info.Module.t_module_type list + method virtual index_module_types : string + end (** A class used to generate html code for info structures. *) @@ -506,14 +567,17 @@ class virtual info = ) l - (** Print html code for a description, except for the [i_params] field. *) - method html_of_info b info_opt = + (** Print html code for a description, except for the [i_params] field. + @param indent can be specified not to use the style of info comments; + default is [true]. + *) + method html_of_info ?(indent=true) b info_opt = match info_opt with None -> () | Some info -> let module M = Odoc_info in - bs b "<div class=\"info\">\n"; + if indent then bs b "<div class=\"info\">\n"; ( match info.M.i_deprecated with None -> () @@ -537,7 +601,7 @@ class virtual info = self#html_of_return_opt b info.M.i_return_value; self#html_of_sees b info.M.i_sees; self#html_of_custom b info.M.i_custom; - bs b "</div>\n" + if indent then bs b "</div>\n" (** Print html code for the first sentence of a description. The titles and lists in this first sentence has been removed.*) @@ -696,45 +760,54 @@ class html = val mutable known_modules_names = StringSet.empty (** The main file. *) - val mutable index = "index.html" + method index = "index.html" (** The file for the index of values. *) - val mutable index_values = "index_values.html" + method index_values = "index_values.html" (** The file for the index of types. *) - val mutable index_types = "index_types.html" + method index_types = "index_types.html" (** The file for the index of exceptions. *) - val mutable index_exceptions = "index_exceptions.html" + method index_exceptions = "index_exceptions.html" (** The file for the index of attributes. *) - val mutable index_attributes = "index_attributes.html" + method index_attributes = "index_attributes.html" (** The file for the index of methods. *) - val mutable index_methods = "index_methods.html" + method index_methods = "index_methods.html" (** The file for the index of classes. *) - val mutable index_classes = "index_classes.html" + method index_classes = "index_classes.html" (** The file for the index of class types. *) - val mutable index_class_types = "index_class_types.html" + method index_class_types = "index_class_types.html" (** The file for the index of modules. *) - val mutable index_modules = "index_modules.html" + method index_modules = "index_modules.html" (** The file for the index of module types. *) - val mutable index_module_types = "index_module_types.html" + method index_module_types = "index_module_types.html" (** The list of attributes. Filled in the [generate] method. *) val mutable list_attributes = [] + method list_attributes = list_attributes (** The list of methods. Filled in the [generate] method. *) val mutable list_methods = [] + method list_methods = list_methods (** The list of values. Filled in the [generate] method. *) val mutable list_values = [] + method list_values = list_values (** The list of exceptions. Filled in the [generate] method. *) val mutable list_exceptions = [] + method list_exceptions = list_exceptions (** The list of types. Filled in the [generate] method. *) val mutable list_types = [] + method list_types = list_types (** The list of modules. Filled in the [generate] method. *) val mutable list_modules = [] + method list_modules = list_modules (** The list of module types. Filled in the [generate] method. *) val mutable list_module_types = [] + method list_module_types = list_module_types (** The list of classes. Filled in the [generate] method. *) val mutable list_classes = [] + method list_classes = list_classes (** The list of class types. Filled in the [generate] method. *) val mutable list_class_types = [] + method list_class_types = list_class_types (** The header of pages. Must be prepared by the [prepare_header] method.*) val mutable header = fun b -> fun ?(nav=None) -> fun ?(comments=[]) -> fun _ -> () @@ -790,7 +863,7 @@ class html = bs b "<head>\n"; bs b style; bs b "<link rel=\"Start\" href=\""; - bs b index; + bs b self#index; bs b "\">\n" ; ( match nav with @@ -810,19 +883,19 @@ class html = ); ( let father = Name.father name in - let href = if father = "" then index else fst (Naming.html_files father) in + let href = if father = "" then self#index else fst (Naming.html_files father) in bp b "<link rel=\"Up\" href=\"%s\">\n" href ) ); - link_if_not_empty list_types Odoc_messages.index_of_types index_types; - link_if_not_empty list_exceptions Odoc_messages.index_of_exceptions index_exceptions; - link_if_not_empty list_values Odoc_messages.index_of_values index_values; - link_if_not_empty list_attributes Odoc_messages.index_of_attributes index_attributes; - link_if_not_empty list_methods Odoc_messages.index_of_methods index_methods; - link_if_not_empty list_classes Odoc_messages.index_of_classes index_classes; - link_if_not_empty list_class_types Odoc_messages.index_of_class_types index_class_types; - link_if_not_empty list_modules Odoc_messages.index_of_modules index_modules; - link_if_not_empty list_module_types Odoc_messages.index_of_module_types index_module_types; + link_if_not_empty self#list_types Odoc_messages.index_of_types self#index_types; + link_if_not_empty self#list_exceptions Odoc_messages.index_of_exceptions self#index_exceptions; + link_if_not_empty self#list_values Odoc_messages.index_of_values self#index_values; + link_if_not_empty self#list_attributes Odoc_messages.index_of_attributes self#index_attributes; + link_if_not_empty self#list_methods Odoc_messages.index_of_methods self#index_methods; + link_if_not_empty self#list_classes Odoc_messages.index_of_classes self#index_classes; + link_if_not_empty self#list_class_types Odoc_messages.index_of_class_types self#index_class_types; + link_if_not_empty self#list_modules Odoc_messages.index_of_modules self#index_modules; + link_if_not_empty self#list_module_types Odoc_messages.index_of_module_types self#index_module_types; let print_one m = let html_file = fst (Naming.html_files m.m_name) in bp b "<link title=\"%s\" rel=\"Chapter\" href=\"%s\">" @@ -894,7 +967,7 @@ class html = ); bs b " "; let father = Name.father name in - let href = if father = "" then index else fst (Naming.html_files father) in + let href = if father = "" then self#index else fst (Naming.html_files father) in bp b "<a href=\"%s\">%s</a>\n" href Odoc_messages.up; bs b " "; ( @@ -1522,7 +1595,7 @@ class html = if info then ( if complete then - self#html_of_info + self#html_of_info ~indent: false else self#html_of_info_first_sentence ) b m.m_info @@ -1551,7 +1624,7 @@ class html = if info then ( if complete then - self#html_of_info + self#html_of_info ~indent: false else self#html_of_info_first_sentence ) b mt.mt_info @@ -1716,7 +1789,7 @@ class html = print_DEBUG "html#html_of_class : info" ; ( if complete then - self#html_of_info + self#html_of_info ~indent: false else self#html_of_info_first_sentence ) b c.cl_info @@ -1758,7 +1831,7 @@ class html = bs b "</pre>"; ( if complete then - self#html_of_info + self#html_of_info ~indent: false else self#html_of_info_first_sentence ) b ct.clt_info @@ -2166,14 +2239,9 @@ class html = @raise Failure if an error occurs.*) method generate_index module_list = try - let chanout = open_out (Filename.concat !Args.target_dir index) in + let chanout = open_out (Filename.concat !Args.target_dir self#index) in let b = new_buf () in let title = match !Args.title with None -> "" | Some t -> self#escape t in - let index_if_not_empty l url m = - match l with - [] -> () - | _ -> bp b "<a href=\"%s\">%s</a><br>\n" url m - in bs b "<html>\n"; self#print_header b self#title; bs b "<body>\n"; @@ -2183,28 +2251,15 @@ class html = let info = Odoc_info.apply_opt Odoc_info.info_of_comment_file !Odoc_info.Args.intro_file in - self#html_of_info b info; - (match info with None -> () | Some _ -> bs b "<br/>"); - index_if_not_empty list_types index_types Odoc_messages.index_of_types; - index_if_not_empty list_exceptions index_exceptions Odoc_messages.index_of_exceptions; - index_if_not_empty list_values index_values Odoc_messages.index_of_values; - index_if_not_empty list_attributes index_attributes Odoc_messages.index_of_attributes; - index_if_not_empty list_methods index_methods Odoc_messages.index_of_methods; - index_if_not_empty list_classes index_classes Odoc_messages.index_of_classes; - index_if_not_empty list_class_types index_class_types Odoc_messages.index_of_class_types; - index_if_not_empty list_modules index_modules Odoc_messages.index_of_modules; - index_if_not_empty list_module_types index_module_types Odoc_messages.index_of_module_types; - bs b "<br>\n<table class=\"indextable\">\n"; - List.iter - (fun m -> - let (html, _) = Naming.html_files m.m_name in - bp b "<tr><td><a href=\"%s\">%s</a></td>" html m.m_name; - bs b "<td>"; - self#html_of_info_first_sentence b m.m_info; - bs b "</td></tr>\n" - ) - module_list; - bs b "</table>\n</body>\n</html>"; + ( + match info with + None -> + self#html_of_Index_list b; + bs b "<br/>"; + self#html_of_Module_list b + (List.map (fun m -> m.m_name) module_list) + | Some i -> self#html_of_info ~indent: false b info + ); Buffer.output_buffer chanout b; close_out chanout with @@ -2214,93 +2269,93 @@ class html = (** Generate the values index in the file [index_values.html]. *) method generate_values_index module_list = self#generate_elements_index - list_values + self#list_values (fun v -> v.val_name) (fun v -> v.val_info) Naming.complete_value_target Odoc_messages.index_of_values - index_values + self#index_values (** Generate the exceptions index in the file [index_exceptions.html]. *) method generate_exceptions_index module_list = self#generate_elements_index - list_exceptions + self#list_exceptions (fun e -> e.ex_name) (fun e -> e.ex_info) Naming.complete_exception_target Odoc_messages.index_of_exceptions - index_exceptions + self#index_exceptions (** Generate the types index in the file [index_types.html]. *) method generate_types_index module_list = self#generate_elements_index - list_types + self#list_types (fun t -> t.ty_name) (fun t -> t.ty_info) Naming.complete_type_target Odoc_messages.index_of_types - index_types + self#index_types (** Generate the attributes index in the file [index_attributes.html]. *) method generate_attributes_index module_list = self#generate_elements_index - list_attributes + self#list_attributes (fun a -> a.att_value.val_name) (fun a -> a.att_value.val_info) Naming.complete_attribute_target Odoc_messages.index_of_attributes - index_attributes + self#index_attributes (** Generate the methods index in the file [index_methods.html]. *) method generate_methods_index module_list = self#generate_elements_index - list_methods + self#list_methods (fun m -> m.met_value.val_name) (fun m -> m.met_value.val_info) Naming.complete_method_target Odoc_messages.index_of_methods - index_methods + self#index_methods (** Generate the classes index in the file [index_classes.html]. *) method generate_classes_index module_list = self#generate_elements_index - list_classes + self#list_classes (fun c -> c.cl_name) (fun c -> c.cl_info) (fun c -> fst (Naming.html_files c.cl_name)) Odoc_messages.index_of_classes - index_classes + self#index_classes (** Generate the class types index in the file [index_class_types.html]. *) method generate_class_types_index module_list = self#generate_elements_index - list_class_types + self#list_class_types (fun ct -> ct.clt_name) (fun ct -> ct.clt_info) (fun ct -> fst (Naming.html_files ct.clt_name)) Odoc_messages.index_of_class_types - index_class_types + self#index_class_types (** Generate the modules index in the file [index_modules.html]. *) method generate_modules_index module_list = self#generate_elements_index - list_modules + self#list_modules (fun m -> m.m_name) (fun m -> m.m_info) (fun m -> fst (Naming.html_files m.m_name)) Odoc_messages.index_of_modules - index_modules + self#index_modules (** Generate the module types index in the file [index_module_types.html]. *) method generate_module_types_index module_list = let module_types = Odoc_info.Search.module_types module_list in self#generate_elements_index - list_module_types + self#list_module_types (fun mt -> mt.mt_name) (fun mt -> mt.mt_info) (fun mt -> fst (Naming.html_files mt.mt_name)) Odoc_messages.index_of_module_types - index_module_types + self#index_module_types (** Generate all the html files from a module list. The main file is [index.html]. *) diff --git a/ocamldoc/odoc_info.ml b/ocamldoc/odoc_info.ml index d142137fc..97dc7b2b0 100644 --- a/ocamldoc/odoc_info.ml +++ b/ocamldoc/odoc_info.ml @@ -46,7 +46,8 @@ and text_element = Odoc_types.text_element = | Ref of string * ref_kind option | Superscript of text | Subscript of text - + | Module_list of string list + | Index_list and text = text_element list diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli index 74c8d59d3..1c724dd45 100644 --- a/ocamldoc/odoc_info.mli +++ b/ocamldoc/odoc_info.mli @@ -49,6 +49,9 @@ and text_element = Odoc_types.text_element = (** A reference to an element. Complete name and kind. *) | Superscript of text (** Superscripts. *) | Subscript of text (** Subscripts. *) + | Module_list of string list + (** The table of the given modules with their abstract. *) + | Index_list (** The links to the various indexes (values, types, ...) *) (** A text is a list of [text_element]. The order matters. *) and text = text_element list diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml index 786581ddc..788a2aaf8 100644 --- a/ocamldoc/odoc_latex.ml +++ b/ocamldoc/odoc_latex.ml @@ -241,6 +241,8 @@ class text = | Odoc_info.Ref (name, ref_opt) -> self#latex_of_Ref fmt name ref_opt | Odoc_info.Superscript t -> self#latex_of_Superscript fmt t | Odoc_info.Subscript t -> self#latex_of_Subscript fmt t + | Odoc_info.Module_list _ -> () + | Odoc_info.Index_list -> () method latex_of_Raw fmt s = ps fmt (self#escape s) diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml index e2c4c19a0..12dc054a9 100644 --- a/ocamldoc/odoc_man.ml +++ b/ocamldoc/odoc_man.ml @@ -269,6 +269,10 @@ class man = bs b "^{"; self#man_of_text2 b t | Odoc_info.Subscript t -> bs b "_{"; self#man_of_text2 b t + | Odoc_info.Module_list _ -> + () + | Odoc_info.Index_list -> + () (** Print groff string to display code. *) method man_of_code b s = self#man_of_text b [ Code s ] diff --git a/ocamldoc/odoc_misc.ml b/ocamldoc/odoc_misc.ml index fe535a618..f0868afba 100644 --- a/ocamldoc/odoc_misc.ml +++ b/ocamldoc/odoc_misc.ml @@ -33,6 +33,33 @@ let input_file_as_string nom = close_in chanin; Buffer.contents buf +let split_string s chars = + let len = String.length s in + let rec iter acc pos = + if pos >= len then + match acc with + "" -> [] + | _ -> [acc] + else + if List.mem s.[pos] chars then + match acc with + "" -> iter "" (pos + 1) + | _ -> acc :: (iter "" (pos + 1)) + else + iter (Printf.sprintf "%s%c" acc s.[pos]) (pos + 1) + in + iter "" 0 + +let split_with_blanks s = split_string s [' ' ; '\n' ; '\r' ; '\t' ] + +let list_concat sep = + let rec iter = function + [] -> [] + | [h] -> [h] + | h :: q -> h :: sep :: q + in + iter + let string_of_longident li = String.concat "." (Longident.flatten li) let get_fields type_expr = @@ -88,6 +115,13 @@ 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 -> + "" in String.concat "" (List.map iter t) @@ -221,6 +255,13 @@ let rec text_no_title_no_list t = | 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)] + | Odoc_types.Module_list l -> + list_concat (Odoc_types.Raw ", ") + (List.map + (fun s -> Odoc_types.Ref (s, Some Odoc_types.RK_module)) + l + ) + | Odoc_types.Index_list -> [] in List.flatten (List.map iter t) @@ -248,6 +289,8 @@ let get_titles_in_text t = | Odoc_types.Link (_, t) | Odoc_types.Superscript t | Odoc_types.Subscript t -> iter_text t + | Odoc_types.Module_list _ -> () + | Odoc_types.Index_list -> () and iter_text te = List.iter iter_ele te in @@ -329,8 +372,9 @@ and first_sentence_text_ele text_ele = | Odoc_types.Link _ | Odoc_types.Ref _ | Odoc_types.Superscript _ - | Odoc_types.Subscript _ -> (false, text_ele, None) - + | Odoc_types.Subscript _ + | Odoc_types.Module_list _ + | Odoc_types.Index_list -> (false, text_ele, None) let first_sentence_of_text t = let (_,t2,_) = first_sentence_text t in diff --git a/ocamldoc/odoc_misc.mli b/ocamldoc/odoc_misc.mli index 4b211b373..982def9db 100644 --- a/ocamldoc/odoc_misc.mli +++ b/ocamldoc/odoc_misc.mli @@ -16,6 +16,9 @@ (** This function returns a file in the form of one string.*) val input_file_as_string : string -> string +(** [split_with_blanks s] splits the given string [s] according to blanks. *) +val split_with_blanks : string -> string list + (** This function creates a string from a Longident.t .*) val string_of_longident : Longident.t -> string diff --git a/ocamldoc/odoc_search.ml b/ocamldoc/odoc_search.ml index 990930d69..d25aee63d 100644 --- a/ocamldoc/odoc_search.ml +++ b/ocamldoc/odoc_search.ml @@ -79,7 +79,9 @@ module Search = | T.Link (_, t) -> search_text root t v | T.List l | T.Enum l -> List.flatten (List.map (fun t -> search_text root t v) l) - | T.Newline -> [] + | T.Newline + | T.Module_list _ + | T.Index_list -> [] | T.Title (n, l_opt, t) -> (match l_opt with None -> [] diff --git a/ocamldoc/odoc_texi.ml b/ocamldoc/odoc_texi.ml index 01626ed13..5eb18ca60 100644 --- a/ocamldoc/odoc_texi.ml +++ b/ocamldoc/odoc_texi.ml @@ -297,6 +297,8 @@ class text = | Ref (name, kind) ->self#texi_of_Ref name kind | Superscript t -> self#texi_of_Superscript t | Subscript t -> self#texi_of_Subscript t + | Odoc_info.Module_list _ -> "" + | Odoc_info.Index_list -> "" method texi_of_Verbatim s = s method texi_of_Raw s = self#escape s diff --git a/ocamldoc/odoc_text.ml b/ocamldoc/odoc_text.ml index b83c88a19..85578098b 100644 --- a/ocamldoc/odoc_text.ml +++ b/ocamldoc/odoc_text.ml @@ -134,6 +134,12 @@ module Texter = ) | Superscript t -> p b "{^" ; p_text b t ; p b "}" | Subscript t -> p b "{_" ; p_text b t ; p b "}" + | Module_list l -> + p b "{!modules:"; + List.iter (fun s -> p b " %s" s) l; + p b "}" + | Index_list -> + p b "{!indexlist}" let string_of_text s = let b = Buffer.create 256 in diff --git a/ocamldoc/odoc_text_lexer.mll b/ocamldoc/odoc_text_lexer.mll index 0a2ca10e8..f0c3738a6 100644 --- a/ocamldoc/odoc_text_lexer.mll +++ b/ocamldoc/odoc_text_lexer.mll @@ -160,8 +160,8 @@ let begin_clt_ref = "{!classtype:"blank_nl | "{!classtype:" let begin_att_ref = "{!attribute:"blank_nl | "{!attribute:" let begin_met_ref = "{!method:"blank_nl | "{!method:" let begin_sec_ref = "{!section:"blank_nl | "{!section:" - - +let begin_mod_list_ref = "{!modules:"blank_nl | "{!modules:" +let index_list = "{!indexlist}" let begin_superscript = "{^"blank_nl | "{^" let begin_subscript = "{_"blank_nl | "{_" @@ -641,6 +641,34 @@ rule main = parse ) } +| begin_mod_list_ref + { + incr_cpts lexbuf ; + if !verb_mode or !latex_mode or !code_pre_mode or !open_brackets >= 1 then + Char (Lexing.lexeme lexbuf) + else + if not !ele_ref_mode then + ( + ele_ref_mode := true; + MOD_LIST_REF + ) + else + ( + Char (Lexing.lexeme lexbuf) + ) + } + +| index_list + { + incr_cpts lexbuf ; + if !verb_mode or !latex_mode or !code_pre_mode or !open_brackets >= 1 then + Char (Lexing.lexeme lexbuf) + else + if not !ele_ref_mode then + INDEX_LIST + else + Char (Lexing.lexeme lexbuf) + } | begin_verb { diff --git a/ocamldoc/odoc_text_parser.mly b/ocamldoc/odoc_text_parser.mly index 2abd562f7..8711ca05f 100644 --- a/ocamldoc/odoc_text_parser.mly +++ b/ocamldoc/odoc_text_parser.mly @@ -60,7 +60,8 @@ let print_DEBUG s = print_string s; print_newline () %token ATT_REF %token MET_REF %token SEC_REF - +%token MOD_LIST_REF +%token INDEX_LIST %token SUPERSCRIPT %token SUBSCRIPT @@ -164,6 +165,13 @@ text_element: let s3 = remove_trailing_blanks s2 in Ref (s3, Some (RK_section [])) } +| MOD_LIST_REF string END { + let s2 = remove_beginning_blanks $2 in + let s3 = remove_trailing_blanks s2 in + let l = Odoc_misc.split_with_blanks s3 in + Module_list l + } +| INDEX_LIST { Index_list } | VERB string END_VERB { Verbatim $2 } | LATEX string END_LATEX { Latex $2 } | LINK string END text END { Link ($2, $4) } diff --git a/ocamldoc/odoc_types.ml b/ocamldoc/odoc_types.ml index fd8938ed6..1bd749c0c 100644 --- a/ocamldoc/odoc_types.ml +++ b/ocamldoc/odoc_types.ml @@ -44,6 +44,8 @@ and text_element = | Ref of string * ref_kind option | Superscript of text | Subscript of text + | Module_list of string list + | Index_list and text = text_element list diff --git a/ocamldoc/odoc_types.mli b/ocamldoc/odoc_types.mli index 61e8db7b2..17eee7490 100644 --- a/ocamldoc/odoc_types.mli +++ b/ocamldoc/odoc_types.mli @@ -49,6 +49,9 @@ and text_element = (** A reference to an element. Complete name and kind. *) | Superscript of text (** Superscripts. *) | Subscript of text (** Subscripts. *) + | Module_list of string list + (** The table of the given modules with their abstract; *) + | Index_list (** The links to the various indexes (values, types, ...) *) (** [text] is a list of text_elements. The order matters. *) and text = text_element list |