]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/ocamldoc/odoc_sig.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / ocamldoc / odoc_sig.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_sig.mli 6661 2004-11-03 09:31:19Z guesdon $ *)
13
14 (** The module for analysing a signature and source code and creating modules, classes, ..., elements.*)
15
16 (** The functions used to retrieve information from a signature. *)
17 module Signature_search :
18     sig
19       type ele
20       type tab = (ele, Types.signature_item) Hashtbl.t
21
22       (** Create a table from a signature. This table is used by some
23          of the search functions below. *)
24       val table : Types.signature -> tab
25
26       (** This function returns the type expression for the value whose name is given,
27          in the given signature.
28          @raise Not_found if error.*)
29       val search_value : tab -> string -> Types.type_expr
30
31       (** This function returns the type expression list for the exception whose name is given,
32          in the given table.
33          @raise Not_found if error.*)
34       val search_exception : tab -> string -> Types.exception_declaration
35
36       (** This function returns the Types.type_declaration  for the type whose name is given,
37          in the given table.
38          @raise Not_found if error.*)
39       val search_type : tab -> string -> Types.type_declaration
40
41       (** This function returns the Types.class_declaration  for the class whose name is given,
42          in the given table.
43          @raise Not_found if error.*)
44       val search_class : tab -> string -> Types.class_declaration
45
46       (** This function returns the Types.cltype_declaration  for the class type whose name is given,
47          in the given table.
48          @raise Not_found if error.*)
49       val search_class_type : tab -> string -> Types.cltype_declaration
50
51       (** This function returns the Types.module_type  for the module whose name is given,
52          in the given table.
53          @raise Not_found if error.*)
54       val search_module : tab -> string -> Types.module_type
55
56       (** This function returns the optional Types.module_type  for the module type whose name is given,
57          in the given table.
58          @raise Not_found if error.*)
59       val search_module_type : tab -> string -> Types.module_type option
60
61       (** This function returns the Types.type_expr  for the given val name
62          in the given class signature.
63          @raise Not_found if error.*)
64       val search_attribute_type :
65           Types.Vars.key -> Types.class_signature -> Types.type_expr
66
67      (** This function returns the Types.type_expr  for the given method name
68         in the given class signature.
69         @raise Not_found if error.*)
70       val search_method_type :
71           string -> Types.class_signature -> Types.type_expr
72     end
73
74 (** Functions to retrieve simple and special comments from strings. *)
75 module type Info_retriever =
76   sig
77     (** Return the couple [(n, list)] where [n] is the number of
78        characters read to retrieve [list], which is the list
79        of special comments found in the string. *)
80     val all_special :
81         string -> string -> int * Odoc_types.info list
82
83     (** Return true if the given string contains a blank line. *)
84     val blank_line_outside_simple :
85         string -> string -> bool
86
87    (** [just_after_special file str] return the pair ([length], [info_opt])
88       where [info_opt] is the first optional special comment found
89       in [str], without any blank line before. [length] is the number
90       of chars from the beginning of [str] to the end of the special comment. *)
91     val just_after_special :
92         string -> string -> (int * Odoc_types.info option)
93
94    (** [first_special file str] return the pair ([length], [info_opt])
95       where [info_opt] is the first optional special comment found
96       in [str]. [length] is the number of chars from the beginning of [str]
97       to the end of the special comment. *)
98     val first_special :
99         string -> string -> (int * Odoc_types.info option)
100
101     (** Return a pair [(comment_opt, element_comment_list)], where [comment_opt] is the last special
102        comment found in the given string and not followed by a blank line,
103        and [element_comment_list] the list of values built from the other
104        special comments found and the given function. *)
105     val get_comments :
106         (Odoc_types.text -> 'a) -> string -> string -> (Odoc_types.info option * 'a list)
107
108   end
109
110 module Analyser :
111   functor (My_ir : Info_retriever) ->
112     sig
113       (** This variable is used to load a file as a string and retrieve characters from it.*)
114       val file : string ref
115
116       (** The name of the analysed file. *)
117       val file_name : string ref
118
119       (** This function takes two indexes (start and end) and return the string
120          corresponding to the indexes in the file global variable. The function
121          prepare_file must have been called to fill the file global variable.*)
122       val get_string_of_file : int -> int -> string
123
124       (** [prepare_file f input_f] sets [file_name] with [f] and loads the file
125          [input_f] into [file].*)
126       val prepare_file : string -> string -> unit
127
128       (** The function used to get the comments in a class. *)
129       val get_comments_in_class : int -> int ->
130         (Odoc_types.info option * Odoc_class.class_element list)
131
132       (** The function used to get the comments in a module. *)
133       val get_comments_in_module : int -> int ->
134         (Odoc_types.info option * Odoc_module.module_element list)
135
136       (** [name_comment_from_type_kind pos_end pos_limit type_kind].
137          This function takes a [Parsetree.type_kind] and returns the list of
138          (name, optional comment) for the various fields/constructors of the type,
139          or an empty list for an abstract type.
140          [pos_end] is last char of the complete type definition.
141          [pos_limit] is the position of the last char we could use to look for a comment,
142          i.e. usually the beginning on the next element.*)
143       val name_comment_from_type_kind :
144           int -> int -> Parsetree.type_kind -> int * (string * Odoc_types.info option) list
145
146       (** This function converts a [Types.type_kind] into a [Odoc_type.type_kind],
147          by associating the comment found in the parsetree of each constructor/field, if any.*)
148       val get_type_kind :
149           Odoc_env.env -> (string * Odoc_types.info option) list ->
150             Types.type_kind -> Odoc_type.type_kind
151
152       (** This function merge two optional info structures. *)
153       val merge_infos :
154           Odoc_types.info option -> Odoc_types.info option ->
155             Odoc_types.info option
156
157       (** Return a module_type_kind from a Parsetree.module_type and a Types.module_type *)
158       val analyse_module_type_kind :
159           Odoc_env.env -> Odoc_name.t ->
160             Parsetree.module_type -> Types.module_type ->
161               Odoc_module.module_type_kind
162
163       (** Analysis of a Parsetree.class_type and a Types.class_type to
164          return a class_type_kind.*)
165       val analyse_class_type_kind : Odoc_env.env ->
166         Odoc_name.t -> int -> Parsetree.class_type -> Types.class_type ->
167           Odoc_class.class_type_kind
168
169       (** This function takes an interface file name, a file containg the code, a parse tree
170          and the signature obtained from the compiler.
171          It goes through the parse tree, creating values for encountered
172          functions, modules, ..., looking in the source file for comments,
173          and in the signature for types information. *)
174       val analyse_signature :
175         string -> string ->
176         Parsetree.signature -> Types.signature -> Odoc_module.t_module
177     end