diff options
Diffstat (limited to 'ocamldoc/odoc_ast.mli')
-rw-r--r-- | ocamldoc/odoc_ast.mli | 58 |
1 files changed, 29 insertions, 29 deletions
diff --git a/ocamldoc/odoc_ast.mli b/ocamldoc/odoc_ast.mli index 53d1105cb..458365b09 100644 --- a/ocamldoc/odoc_ast.mli +++ b/ocamldoc/odoc_ast.mli @@ -26,66 +26,66 @@ module Typedtree_search : val tables : Typedtree.structure_item list -> tab * tab_values (** This function returns the [Typedtree.module_expr] associated to the given module name, - in the given table. - @raise Not_found if the module was not found.*) + in the given table. + @raise Not_found if the module was not found.*) val search_module : tab -> string -> Typedtree.module_expr (** This function returns the [Types.module_type] associated to the given module type name, - in the given table. - @raise Not_found if the module type was not found.*) + in the given table. + @raise Not_found if the module type was not found.*) val search_module_type : tab -> string -> Types.module_type (** This function returns the [Types.exception_declaration] associated to the given exception name, - in the given table. - @raise Not_found if the exception was not found.*) + in the given table. + @raise Not_found if the exception was not found.*) val search_exception : tab -> string -> Types.exception_declaration (** This function returns the [Path.t] associated to the given exception rebind name, - in the table. - @raise Not_found if the exception rebind was not found.*) + in the table. + @raise Not_found if the exception rebind was not found.*) val search_exception_rebind : tab -> string -> Path.t (** This function returns the [Typedtree.type_declaration] associated to the given type name, - in the given table. - @raise Not_found if the type was not found. *) + in the given table. + @raise Not_found if the type was not found. *) val search_type_declaration : tab -> string -> Types.type_declaration (** This function returns the [Typedtree.class_expr] and type parameters - associated to the given class name, in the given table. - @raise Not_found if the class was not found. *) + associated to the given class name, in the given table. + @raise Not_found if the class was not found. *) val search_class_exp : tab -> string -> (Typedtree.class_expr * (Types.type_expr list)) (** This function returns the [Types.cltype_declaration] associated to the given class type name, - in the given table. - @raise Not_found if the class type was not found. *) + in the given table. + @raise Not_found if the class type was not found. *) val search_class_type_declaration : tab -> string -> Types.cltype_declaration (** This function returns the couple (pat, exp) for the given value name, in the - given table of values. - @raise Not found if no value matches the name.*) + given table of values. + @raise Not found if no value matches the name.*) val search_value : tab_values -> string -> Typedtree.pattern * Typedtree.expression (** This function returns the [type_expr] for the given primitive name, in the - given table. - @raise Not found if no value matches the name.*) + given table. + @raise Not found if no value matches the name.*) val search_primitive : tab -> string -> Types.type_expr (** This function returns the [Typedtree.class_expr] associated to - the n'th inherit in the given class structure of typed tree. - @raise Not_found if the class expression could not be found.*) + the n'th inherit in the given class structure of typed tree. + @raise Not_found if the class expression could not be found.*) val get_nth_inherit_class_expr : - Typedtree.class_structure -> int -> Typedtree.class_expr + Typedtree.class_structure -> int -> Typedtree.class_expr (** This function returns the [Types.type_expr] of the attribute - whose name is given, in a given class structure. - @raise Not_found if the class attribute could not be found.*) + whose name is given, in a given class structure. + @raise Not_found if the class attribute could not be found.*) val search_attribute_type : - Typedtree.class_structure -> string -> Types.type_expr + Typedtree.class_structure -> string -> Types.type_expr (** This function returns the [Types.expression] of the method whose name is given, in a given class structure. - @raise Not_found if the class method could not be found.*) + @raise Not_found if the class method could not be found.*) val search_method_expression : - Typedtree.class_structure -> string -> Typedtree.expression + Typedtree.class_structure -> string -> Typedtree.expression end (** The module which performs the analysis of a typed tree. @@ -95,9 +95,9 @@ module Analyser : functor (My_ir : Odoc_sig.Info_retriever) -> sig (** This function takes a file name, a file containg the code and - the typed tree obtained from the compiler. - It goes through the tree, creating values for encountered - functions, modules, ..., and looking in the source file for comments.*) + the typed tree obtained from the compiler. + It goes through the tree, creating values for encountered + functions, modules, ..., and looking in the source file for comments.*) val analyse_typed_tree : string -> string -> Parsetree.structure -> typedtree -> Odoc_module.t_module end |