]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/ocamldoc/odoc_ast.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / ocamldoc / odoc_ast.mli
1 (***********************************************************************)
2 (*                             OCamldoc                                *)
3 (*                                                                     *)
4 (*            Maxence Guesdon, projet Cristal, INRIA Rocquencourt      *)
5 (*                                                                     *)
6 (*  Copyright 2001 Institut National de Recherche en Informatique et   *)
7 (*  en Automatique.  All rights reserved.  This file is distributed    *)
8 (*  under the terms of the Q Public License version 1.0.               *)
9 (*                                                                     *)
10 (***********************************************************************)
11
12 (* $Id: odoc_ast.mli 5973 2003-11-24 10:44:07Z starynke $ *)
13
14 (** The module for analysing the typed abstract syntax tree and source code and creating modules, classes, ..., elements.*)
15
16 type typedtree = Typedtree.structure * Typedtree.module_coercion
17
18 (** This module is used to search for structure items by name in a [Typedtree.structure]. *)
19 module Typedtree_search :
20     sig
21       type ele
22
23       type tab = (ele, Typedtree.structure_item) Hashtbl.t
24       type tab_values = (Odoc_name.t, Typedtree.pattern * Typedtree.expression) Hashtbl.t
25
26       (** Create hash tables used to search by some of the functions below. *)
27       val tables : Typedtree.structure_item list -> tab * tab_values
28
29       (** This function returns the [Typedtree.module_expr] associated to the given module name,
30          in the given table.
31          @raise Not_found if the module was not found.*)
32       val search_module : tab -> string -> Typedtree.module_expr
33
34       (** This function returns the [Types.module_type] associated to the given module type name,
35          in the given table.
36          @raise Not_found if the module type was not found.*)
37       val search_module_type : tab -> string -> Types.module_type
38
39       (** This function returns the [Types.exception_declaration] associated to the given exception name,
40          in the given table.
41          @raise Not_found if the exception was not found.*)
42       val search_exception : tab -> string -> Types.exception_declaration
43
44       (** This function returns the [Path.t] associated to the given exception rebind name,
45          in the table. 
46          @raise Not_found if the exception rebind was not found.*)
47       val search_exception_rebind : tab -> string -> Path.t
48
49       (** This function returns the [Typedtree.type_declaration] associated to the given type name,
50          in the given table.
51          @raise Not_found if the type was not found. *)
52       val search_type_declaration : tab -> string -> Types.type_declaration
53
54       (** This function returns the [Typedtree.class_expr] and type parameters 
55          associated to the given class name, in the given table.
56          @raise Not_found if the class was not found. *)
57       val search_class_exp : tab -> string -> (Typedtree.class_expr * (Types.type_expr list))
58
59       (** This function returns the [Types.cltype_declaration] associated to the given class type name,
60          in the given table.
61          @raise Not_found if the class type was not found. *)
62       val search_class_type_declaration : tab -> string -> Types.cltype_declaration
63
64       (** This function returns the couple (pat, exp) for the given value name, in the 
65          given table of values.
66          @raise Not found if no value matches the name.*)
67       val search_value : tab_values -> string -> Typedtree.pattern * Typedtree.expression
68
69       (** This function returns the [type_expr] for the given primitive name, in the 
70          given table.
71          @raise Not found if no value matches the name.*)
72       val search_primitive : tab -> string -> Types.type_expr
73
74       (** This function returns the [Typedtree.class_expr] associated to 
75          the n'th inherit in the given class structure of typed tree. 
76          @raise Not_found if the class expression could not be found.*)
77       val get_nth_inherit_class_expr :
78           Typedtree.class_structure -> int -> Typedtree.class_expr
79
80       (** This function returns the [Types.type_expr] of the attribute 
81          whose name is given, in a given class structure.
82          @raise Not_found if the class attribute could not be found.*)
83       val search_attribute_type :
84           Typedtree.class_structure -> string -> Types.type_expr
85
86       (** This function returns the [Types.expression] of the method whose name is given, in a given class structure.
87          @raise Not_found if the class method could not be found.*)
88       val search_method_expression :
89           Typedtree.class_structure -> string -> Typedtree.expression
90     end
91     
92 (** The module which performs the analysis of a typed tree. 
93    The module uses the module {!Odoc_sig.Analyser}.
94    @param My_ir The module used to retrieve comments and special comments.*)
95 module Analyser :
96   functor (My_ir : Odoc_sig.Info_retriever) ->
97     sig
98       (** This function takes a file name, a file containg the code and 
99          the typed tree obtained from the compiler. 
100          It goes through the tree, creating values for encountered
101          functions, modules, ..., and looking in the source file for comments.*)
102       val analyse_typed_tree :
103         string -> string -> Parsetree.structure -> typedtree -> Odoc_module.t_module
104     end