]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamldoc/odoc_info.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / ocamldoc / odoc_info.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_info.mli 8932 2008-07-25 13:28:23Z guesdon $ *)
13
14 (** Interface to the information collected in source files. *)
15
16 (** The differents kinds of element references. *)
17 type ref_kind = Odoc_types.ref_kind =
18     RK_module
19   | RK_module_type
20   | RK_class
21   | RK_class_type
22   | RK_value
23   | RK_type
24   | RK_exception
25   | RK_attribute
26   | RK_method
27   | RK_section of text
28
29 and text_element = Odoc_types.text_element =
30   | Raw of string (** Raw text. *)
31   | Code of string (** The string is source code. *)
32   | CodePre of string (** The string is pre-formatted source code. *)
33   | Verbatim of string (** String 'as is'. *)
34   | Bold of text (** Text in bold style. *)
35   | Italic of text (** Text in italic. *)
36   | Emphasize of text (** Emphasized text. *)
37   | Center of text (** Centered text. *)
38   | Left of text (** Left alignment. *)
39   | Right of text (** Right alignment. *)
40   | List of text list (** A list. *)
41   | Enum of text list (** An enumerated list. *)
42   | Newline   (** To force a line break. *)
43   | Block of text (** Like html's block quote. *)
44   | Title of int * string option * text
45              (** Style number, optional label, and text. *)
46   | Latex of string (** A string for latex. *)
47   | Link of string * text (** A reference string and the link text. *)
48   | Ref of string * ref_kind option
49        (** A reference to an element. Complete name and kind. *)
50   | Superscript of text (** Superscripts. *)
51   | Subscript of text (** Subscripts. *)
52   | Module_list of string list
53        (** The table of the given modules with their abstract. *)
54   | Index_list (** The links to the various indexes (values, types, ...) *)
55   | Custom of string * text (** to extend \{foo syntax *)
56
57 (** A text is a list of [text_element]. The order matters. *)
58 and text = text_element list
59
60 (** The different forms of references in \@see tags. *)
61 type see_ref = Odoc_types.see_ref =
62     See_url of string
63   | See_file of string
64   | See_doc of string
65
66 (** Raised when parsing string to build a {!Odoc_info.text}
67    structure. [(line, char, string)] *)
68 exception Text_syntax of int * int * string
69
70 (** The information in a \@see tag. *)
71 type see = see_ref * text
72
73 (** Parameter name and description. *)
74 type param = (string * text)
75
76 (** Raised exception name and description. *)
77 type raised_exception = (string * text)
78
79 (** Information in a special comment *)
80 type info = Odoc_types.info = {
81     i_desc : text option; (** The description text. *)
82     i_authors : string list; (** The list of authors in \@author tags. *)
83     i_version : string option; (** The string in the \@version tag. *)
84     i_sees : see list; (** The list of \@see tags. *)
85     i_since : string option; (** The string in the \@since tag. *)
86     i_deprecated : text option; (** The of the \@deprecated tag. *)
87     i_params : param list; (** The list of parameter descriptions. *)
88     i_raised_exceptions : raised_exception list; (** The list of raised exceptions. *)
89     i_return_value : text option; (** The description text of the return value. *)
90     i_custom : (string * text) list ; (** A text associated to a custom @-tag. *)
91   }
92
93 (** Location of elements in implementation and interface files. *)
94 type location = Odoc_types.location = {
95     loc_impl : (string * int) option ; (** implementation file name and position *)
96     loc_inter : (string * int) option ; (** interface file name and position *)
97   }
98
99 (** A dummy location. *)
100 val dummy_loc : location
101
102 (** Representation of element names. *)
103 module Name :
104     sig
105       type t = string
106
107       (** Access to the simple name. *)
108       val simple : t -> t
109
110       (** [concat t1 t2] returns the concatenation of [t1] and [t2].*)
111       val concat : t -> t -> t
112
113       (** Return the depth of the name, i.e. the numer of levels to the root.
114          Example : [depth "Toto.Tutu.name"] = [3]. *)
115       val depth : t -> int
116
117       (** Take two names n1 and n2 = n3.n4 and return n4 if n3=n1 or else n2. *)
118       val get_relative : t -> t -> t
119
120       (** Return the name of the 'father' (like [dirname] for a file name).*)
121       val father : t -> t
122     end
123
124 (** Representation and manipulation of method / function / class / module parameters.*)
125 module Parameter :
126   sig
127     (** {3 Types} *)
128     (** Representation of a simple parameter name *)
129     type simple_name = Odoc_parameter.simple_name =
130         {
131           sn_name : string ;
132           sn_type : Types.type_expr ;
133           mutable sn_text : text option ;
134         }
135
136     (** Representation of parameter names. We need it to represent parameter names in tuples.
137        The value [Tuple ([], t)] stands for an anonymous parameter.*)
138     type param_info = Odoc_parameter.param_info =
139         Simple_name of simple_name
140       | Tuple of param_info list * Types.type_expr
141
142     (** A parameter is just a param_info.*)
143     type parameter = param_info
144
145     (** {3 Functions} *)
146     (** Acces to the name as a string. For tuples, parenthesis and commas are added. *)
147     val complete_name : parameter -> string
148
149     (** Access to the complete type. *)
150     val typ : parameter -> Types.type_expr
151
152     (** Access to the list of names ; only one for a simple parameter, or
153        a list for a tuple. *)
154     val names : parameter -> string list
155
156     (** Access to the description of a specific name.
157        @raise Not_found if no description is associated to the given name. *)
158     val desc_by_name : parameter -> string -> text option
159
160     (** Access to the type of a specific name.
161        @raise Not_found if no type is associated to the given name. *)
162     val type_by_name : parameter -> string -> Types.type_expr
163   end
164
165 (** Representation and manipulation of exceptions. *)
166 module Exception :
167   sig
168     (** Used when the exception is a rebind of another exception,
169        when we have [exception Ex = Target_ex].*)
170     type exception_alias = Odoc_exception.exception_alias =
171         {
172           ea_name : Name.t ; (** The complete name of the target exception. *)
173           mutable ea_ex : t_exception option ; (** The target exception, if we found it.*)
174         }
175
176     and t_exception = Odoc_exception.t_exception =
177         {
178           ex_name : Name.t ;
179           mutable ex_info : info option ; (** Information found in the optional associated comment. *)
180           ex_args : Types.type_expr list ; (** The types of the parameters. *)
181           ex_alias : exception_alias option ; (** [None] when the exception is not a rebind. *)
182           mutable ex_loc : location ;
183           mutable ex_code : string option ;
184         }
185   end
186
187 (** Representation and manipulation of types.*)
188 module Type :
189   sig
190     type private_flag = Odoc_type.private_flag =
191       Private | Public
192
193     (** Description of a variant type constructor. *)
194     type variant_constructor = Odoc_type.variant_constructor =
195         {
196           vc_name : string ; (** Name of the constructor. *)
197           vc_args : Types.type_expr list ; (** Arguments of the constructor. *)
198           mutable vc_text : text option ; (** Optional description in the associated comment. *)
199         }
200
201     (** Description of a record type field. *)
202     type record_field = Odoc_type.record_field =
203         {
204           rf_name : string ; (** Name of the field. *)
205           rf_mutable : bool ; (** [true] if mutable. *)
206           rf_type : Types.type_expr ; (** Type of the field. *)
207           mutable rf_text : text option ; (** Optional description in the associated comment.*)
208         }
209
210     (** The various kinds of a type. *)
211     type type_kind = Odoc_type.type_kind =
212         Type_abstract (** Type is abstract, for example [type t]. *)
213       | Type_variant of variant_constructor list
214                    (** constructors *)
215       | Type_record of record_field list
216                    (** fields *)
217
218     (** Representation of a type. *)
219     type t_type = Odoc_type.t_type =
220         {
221           ty_name : Name.t ; (** Complete name of the type. *)
222           mutable ty_info : info option ; (** Information found in the optional associated comment. *)
223           ty_parameters : (Types.type_expr * bool * bool) list ;
224                     (** type parameters: (type, covariant, contravariant) *)
225           ty_kind : type_kind; (** Type kind. *)
226           ty_private : private_flag; (** Private or public type. *)
227           ty_manifest : Types.type_expr option; (** Type manifest. *)
228           mutable ty_loc : location ;
229           mutable ty_code : string option;
230         }
231
232   end
233
234 (** Representation and manipulation of values, class attributes and class methods. *)
235 module Value :
236   sig
237     (** Representation of a value. *)
238     type t_value = Odoc_value.t_value =
239         {
240           val_name : Name.t ; (** Complete name of the value. *)
241           mutable val_info : info option ; (** Information found in the optional associated comment. *)
242           val_type : Types.type_expr ; (** Type of the value. *)
243           val_recursive : bool ; (** [true] if the value is recursive. *)
244           mutable val_parameters : Odoc_parameter.parameter list ; (** The parameters, if any. *)
245           mutable val_code : string option ; (** The code of the value, if we had the only the implementation file. *)
246           mutable val_loc : location ;
247         }
248
249     (** Representation of a class attribute. *)
250     type t_attribute = Odoc_value.t_attribute =
251         {
252           att_value : t_value ; (** an attribute has almost all the same information as a value *)
253           att_mutable : bool ;  (** [true] if the attribute is mutable. *)
254           att_virtual : bool ;  (** [true] if the attribute is virtual. *)
255         }
256
257     (** Representation of a class method. *)
258     type t_method = Odoc_value.t_method =
259         {
260           met_value : t_value ; (** a method has almost all the same information as a value *)
261           met_private : bool ;  (** [true] if the method is private.*)
262           met_virtual : bool ;  (** [true] if the method is virtual. *)
263         }
264
265     (** Return [true] if the value is a function, i.e. it has a functional type. *)
266     val is_function : t_value -> bool
267
268     (** Access to the description associated to the given parameter name.*)
269     val value_parameter_text_by_name : t_value -> string -> text option
270   end
271
272 (** Representation and manipulation of classes and class types.*)
273 module Class :
274   sig
275     (** {3 Types} *)
276     (** To keep the order of elements in a class. *)
277     type class_element = Odoc_class.class_element =
278         Class_attribute of Value.t_attribute
279       | Class_method of Value.t_method
280       | Class_comment of text
281
282     (** Used when we can reference a t_class or a t_class_type. *)
283     type cct = Odoc_class.cct =
284         Cl of t_class
285       | Cltype of t_class_type * Types.type_expr list (** Class type and type parameters. *)
286
287     and inherited_class = Odoc_class.inherited_class =
288         {
289           ic_name : Name.t ; (** Complete name of the inherited class. *)
290           mutable ic_class : cct option ; (** The associated t_class or t_class_type. *)
291           ic_text : text option ; (** The inheritance description, if any. *)
292         }
293
294     and class_apply = Odoc_class.class_apply =
295         {
296           capp_name : Name.t ; (** The complete name of the applied class. *)
297           mutable capp_class : t_class option;  (** The associated t_class if we found it. *)
298           capp_params : Types.type_expr list; (** The type of expressions the class is applied to. *)
299           capp_params_code : string list ; (** The code of these exprssions. *)
300         }
301
302     and class_constr = Odoc_class.class_constr =
303         {
304           cco_name : Name.t ; (** The complete name of the applied class. *)
305           mutable cco_class : cct option;
306               (** The associated class or class type if we found it. *)
307           cco_type_parameters : Types.type_expr list; (** The type parameters of the class, if needed. *)
308         }
309
310     and class_kind = Odoc_class.class_kind =
311         Class_structure of inherited_class list * class_element list
312         (** An explicit class structure, used in implementation and interface. *)
313       | Class_apply of class_apply
314         (** Application/alias of a class, used in implementation only. *)
315       | Class_constr of class_constr
316         (** A class used to give the type of the defined class,
317            instead of a structure, used in interface only.
318            For example, it will be used with the name [M1.M2....bar]
319            when the class foo is defined like this :
320            [class foo : int -> bar] *)
321       | Class_constraint of class_kind * class_type_kind
322         (** A class definition with a constraint. *)
323
324     (** Representation of a class. *)
325     and t_class = Odoc_class.t_class =
326         {
327           cl_name : Name.t ; (** Complete name of the class. *)
328           mutable cl_info : info option ; (** Information found in the optional associated comment. *)
329           cl_type : Types.class_type ; (** Type of the class. *)
330           cl_type_parameters : Types.type_expr list ; (** Type parameters. *)
331           cl_virtual : bool ; (** [true] when the class is virtual. *)
332           mutable cl_kind : class_kind ; (** The way the class is defined. *)
333           mutable cl_parameters : Parameter.parameter list ; (** The parameters of the class. *)
334           mutable cl_loc : location ;
335         }
336
337     and class_type_alias = Odoc_class.class_type_alias =
338         {
339           cta_name : Name.t ; (** Complete name of the target class type. *)
340           mutable cta_class : cct option ;  (** The target t_class or t_class_type, if we found it.*)
341           cta_type_parameters : Types.type_expr list ; (** The type parameters. A VOIR : mettre des string ? *)
342         }
343
344     and class_type_kind = Odoc_class.class_type_kind =
345         Class_signature of inherited_class list * class_element list
346       | Class_type of class_type_alias (** A class type eventually applied to type args. *)
347
348     (** Representation of a class type. *)
349     and t_class_type = Odoc_class.t_class_type =
350         {
351           clt_name : Name.t ; (** Complete name of the type. *)
352           mutable clt_info : info option ; (** Information found in the optional associated comment. *)
353           clt_type : Types.class_type ;
354           clt_type_parameters : Types.type_expr list ; (** Type parameters. *)
355           clt_virtual : bool ; (** [true] if the class type is virtual *)
356           mutable clt_kind : class_type_kind ; (** The way the class type is defined. *)
357           mutable clt_loc : location ;
358         }
359
360     (** {3 Functions} *)
361
362     (** Access to the elements of a class. *)
363     val class_elements : ?trans:bool -> t_class -> class_element list
364
365     (** Access to the list of class attributes. *)
366     val class_attributes : ?trans:bool -> t_class -> Value.t_attribute list
367
368     (** Access to the description associated to the given class parameter name. *)
369     val class_parameter_text_by_name : t_class -> string -> text option
370
371     (** Access to the methods of a class. *)
372     val class_methods : ?trans:bool -> t_class -> Value.t_method list
373
374     (** Access to the comments of a class. *)
375     val class_comments : ?trans:bool -> t_class -> text list
376
377     (** Access to the elements of a class type. *)
378     val class_type_elements : ?trans:bool -> t_class_type -> class_element list
379
380     (** Access to the list of class type attributes. *)
381     val class_type_attributes : ?trans:bool -> t_class_type -> Value.t_attribute list
382
383     (** Access to the description associated to the given class type parameter name. *)
384     val class_type_parameter_text_by_name : t_class_type -> string -> text option
385
386     (** Access to the methods of a class type. *)
387     val class_type_methods : ?trans:bool -> t_class_type -> Value.t_method list
388
389     (** Access to the comments of a class type. *)
390     val class_type_comments : ?trans:bool -> t_class_type -> text list
391   end
392
393 (** Representation and manipulation of modules and module types. *)
394 module Module :
395   sig
396     (** {3 Types} *)
397     (** To keep the order of elements in a module. *)
398     type module_element = Odoc_module.module_element =
399         Element_module of t_module
400       | Element_module_type of t_module_type
401       | Element_included_module of included_module
402       | Element_class of Class.t_class
403       | Element_class_type of Class.t_class_type
404       | Element_value of Value.t_value
405       | Element_exception of Exception.t_exception
406       | Element_type of Type.t_type
407       | Element_module_comment of text
408
409     (** Used where we can reference t_module or t_module_type. *)
410     and mmt = Odoc_module.mmt =
411       | Mod of t_module
412       | Modtype of t_module_type
413
414     and included_module = Odoc_module.included_module =
415         {
416           im_name : Name.t ; (** Complete name of the included module. *)
417           mutable im_module : mmt option ; (** The included module or module type, if we found it. *)
418           mutable im_info : Odoc_types.info option ; (** comment associated to the includ directive *)
419         }
420
421     and module_alias = Odoc_module.module_alias =
422         {
423           ma_name : Name.t ; (** Complete name of the target module. *)
424           mutable ma_module : mmt option ; (** The real module or module type if we could associate it. *)
425         }
426
427     and module_parameter = Odoc_module.module_parameter = {
428         mp_name : string ; (** the name *)
429         mp_type : Types.module_type ; (** the type *)
430         mp_type_code : string ; (** the original code *)
431         mp_kind : module_type_kind ; (** the way the parameter was built *)
432       }
433
434     (** Different kinds of a module. *)
435     and module_kind = Odoc_module.module_kind =
436       | Module_struct of module_element list (** A complete module structure. *)
437       | Module_alias of module_alias (** Complete name and corresponding module if we found it *)
438       | Module_functor of module_parameter * module_kind
439                      (** A functor, with its parameter and the rest of its definition *)
440       | Module_apply of module_kind * module_kind
441                      (** A module defined by application of a functor. *)
442       | Module_with of module_type_kind * string
443                      (** A module whose type is a with ... constraint.
444                         Should appear in interface files only. *)
445       | Module_constraint of module_kind * module_type_kind
446                      (** A module constraint by a module type. *)
447
448     (** Representation of a module. *)
449     and t_module = Odoc_module.t_module =
450         {
451           m_name : Name.t ; (** Complete name of the module. *)
452           mutable m_type : Types.module_type ; (** The type of the module. *)
453           mutable m_info : info option ; (** Information found in the optional associated comment. *)
454           m_is_interface : bool ; (** [true] for modules read from interface files *)
455           m_file : string ; (** The file the module is defined in. *)
456           mutable m_kind : module_kind ; (** The way the module is defined. *)
457           mutable m_loc : location ;
458           mutable m_top_deps : Name.t list ; (** The toplevels module names this module depends on. *)
459           mutable m_code : string option ; (** The whole code of the module *)
460           mutable m_code_intf : string option ; (** The whole code of the interface of the module *)
461           m_text_only : bool ; (** [true] if the module comes from a text file *)
462         }
463
464     and module_type_alias = Odoc_module.module_type_alias =
465         {
466           mta_name : Name.t ; (** Complete name of the target module type. *)
467           mutable mta_module : t_module_type option ; (** The real module type if we could associate it. *)
468         }
469
470     (** Different kinds of module type. *)
471     and module_type_kind = Odoc_module.module_type_kind =
472       | Module_type_struct of module_element list (** A complete module signature. *)
473       | Module_type_functor of module_parameter * module_type_kind
474             (** A functor, with its parameter and the rest of its definition *)
475       | Module_type_alias of module_type_alias
476             (** Complete alias name and corresponding module type if we found it. *)
477       | Module_type_with of module_type_kind * string
478             (** The module type kind and the code of the with constraint. *)
479
480     (** Representation of a module type. *)
481     and t_module_type = Odoc_module.t_module_type =
482         {
483           mt_name : Name.t ; (** Complete name of the module type. *)
484           mutable mt_info : info option ; (** Information found in the optional associated comment. *)
485           mutable mt_type : Types.module_type option ; (** [None] means that the module type is abstract. *)
486           mt_is_interface : bool ; (** [true] for modules read from interface files. *)
487           mt_file : string ; (** The file the module type is defined in. *)
488           mutable mt_kind : module_type_kind option ;
489               (** The way the module is defined. [None] means that module type is abstract.
490                  It is always [None] when the module type was extracted from the implementation file.
491                  That means module types are only analysed in interface files. *)
492           mutable mt_loc : location ;
493         }
494
495     (** {3 Functions for modules} *)
496
497     (** Access to the elements of a module. *)
498     val module_elements : ?trans:bool -> t_module -> module_element list
499
500     (** Access to the submodules of a module. *)
501     val module_modules : ?trans:bool -> t_module -> t_module list
502
503     (** Access to the module types of a module. *)
504     val module_module_types : ?trans:bool -> t_module -> t_module_type list
505
506     (** Access to the included modules of a module. *)
507     val module_included_modules : ?trans:bool-> t_module -> included_module list
508
509     (** Access to the exceptions of a module. *)
510     val module_exceptions : ?trans:bool-> t_module -> Exception.t_exception list
511
512     (** Access to the types of a module. *)
513     val module_types : ?trans:bool-> t_module -> Type.t_type list
514
515     (** Access to the values of a module. *)
516     val module_values : ?trans:bool -> t_module -> Value.t_value list
517
518     (** Access to functional values of a module. *)
519     val module_functions : ?trans:bool-> t_module -> Value.t_value list
520
521     (** Access to non-functional values of a module. *)
522     val module_simple_values : ?trans:bool-> t_module -> Value.t_value list
523
524     (** Access to the classes of a module. *)
525     val module_classes : ?trans:bool-> t_module -> Class.t_class list
526
527     (** Access to the class types of a module. *)
528     val module_class_types : ?trans:bool-> t_module -> Class.t_class_type list
529
530     (** The list of classes defined in this module and all its submodules and functors. *)
531     val module_all_classes : ?trans:bool-> t_module -> Class.t_class list
532
533     (** [true] if the module is functor. *)
534     val module_is_functor : t_module -> bool
535
536     (** The list of couples (module parameter, optional description). *)
537     val module_parameters : ?trans:bool-> t_module -> (module_parameter * text option) list
538
539     (** The list of module comments. *)
540     val module_comments : ?trans:bool-> t_module -> text list
541
542     (** {3 Functions for module types} *)
543
544     (** Access to the elements of a module type. *)
545     val module_type_elements : ?trans:bool-> t_module_type -> module_element list
546
547     (** Access to the submodules of a module type. *)
548     val module_type_modules : ?trans:bool-> t_module_type -> t_module list
549
550     (** Access to the module types of a module type. *)
551     val module_type_module_types : ?trans:bool-> t_module_type -> t_module_type list
552
553     (** Access to the included modules of a module type. *)
554     val module_type_included_modules : ?trans:bool-> t_module_type -> included_module list
555
556     (** Access to the exceptions of a module type. *)
557     val module_type_exceptions : ?trans:bool-> t_module_type -> Exception.t_exception list
558
559     (** Access to the types of a module type. *)
560     val module_type_types : ?trans:bool-> t_module_type -> Type.t_type list
561
562     (** Access to the values of a module type. *)
563     val module_type_values : ?trans:bool-> t_module_type -> Value.t_value list
564
565     (** Access to functional values of a module type. *)
566     val module_type_functions : ?trans:bool-> t_module_type -> Value.t_value list
567
568     (** Access to non-functional values of a module type. *)
569     val module_type_simple_values : ?trans:bool-> t_module_type -> Value.t_value list
570
571     (** Access to the classes of a module type. *)
572     val module_type_classes : ?trans:bool-> t_module_type -> Class.t_class list
573
574     (** Access to the class types of a module type. *)
575     val module_type_class_types : ?trans:bool-> t_module_type -> Class.t_class_type list
576
577     (** The list of classes defined in this module type and all its submodules and functors. *)
578     val module_type_all_classes : ?trans:bool-> t_module_type -> Class.t_class list
579
580     (** [true] if the module type is functor. *)
581     val module_type_is_functor : t_module_type -> bool
582
583     (** The list of couples (module parameter, optional description). *)
584     val module_type_parameters : ?trans:bool-> t_module_type -> (module_parameter * text option) list
585
586     (** The list of module comments. *)
587     val module_type_comments : ?trans:bool-> t_module_type -> text list
588   end
589
590
591 (** {3 Getting strings from values} *)
592
593 (** This function is used to reset the names of type variables.
594    It must be called when printing the whole type of a function,
595    but not when printing the type of its parameters. Same for
596    classes (call it) and methods and attributes (don't call it).*)
597 val reset_type_names : unit -> unit
598
599 (** [string_of_variance t (covariant, invariant)] returns ["+"] if
600    the given information means "covariant", ["-"] if the it means
601    "contravariant", orelse [""], and always [""] if the given
602    type is not an abstract type with no manifest (i.e. no need
603    for the variance to be printed.*)
604 val string_of_variance : Type.t_type -> (bool * bool) -> string
605
606 (** This function returns a string representing a Types.type_expr. *)
607 val string_of_type_expr : Types.type_expr -> string
608
609 (** @return a string to display the parameters of the given class,
610    in the same form as the compiler. *)
611 val string_of_class_params : Class.t_class -> string
612
613 (** This function returns a string to represent the given list of types,
614    with a given separator. *)
615 val string_of_type_list : ?par: bool -> string -> Types.type_expr list -> string
616
617 (** This function returns a string to represent the list of type parameters
618    for the given type. *)
619 val string_of_type_param_list : Type.t_type -> string
620
621 (** This function returns a string to represent the given list of
622    type parameters of a class or class type,
623    with a given separator. *)
624 val string_of_class_type_param_list : Types.type_expr list -> string
625
626 (** This function returns a string representing a [Types.module_type].
627    @param complete indicates if we must print complete signatures
628    or just [sig end]. Default if [false].
629    @param code if [complete = false] and the type contains something else
630    than identificators and functors, then the given code is used.
631 *)
632 val string_of_module_type : ?code: string -> ?complete: bool -> Types.module_type -> string
633
634 (** This function returns a string representing a [Types.class_type].
635    @param complete indicates if we must print complete signatures
636    or just [object end]. Default if [false].
637 *)
638 val string_of_class_type : ?complete: bool -> Types.class_type -> string
639
640
641 (** Get a string from a text. *)
642 val string_of_text : text -> string
643
644 (** Get a string from an info structure. *)
645 val string_of_info : info -> string
646
647 (** @return a string to describe the given type. *)
648 val string_of_type : Type.t_type -> string
649
650 (** @return a string to describe the given exception. *)
651 val string_of_exception : Exception.t_exception -> string
652
653 (** @return a string to describe the given value. *)
654 val string_of_value : Value.t_value -> string
655
656 (** @return a string to describe the given attribute. *)
657 val string_of_attribute : Value.t_attribute -> string
658
659 (** @return a string to describe the given method. *)
660 val string_of_method : Value.t_method -> string
661
662 (** {3 Miscelaneous functions} *)
663
664 (** Return the first sentence (until the first dot followed by a blank
665    or the first blank line) of a text.
666    Don't stop in the middle of [Code], [CodePre], [Verbatim], [List], [Enum],
667    [Latex], [Link], [Ref], [Subscript] or [Superscript]. *)
668 val first_sentence_of_text : text -> text
669
670 (** Return the first sentence (until the first dot followed by a blank
671    or the first blank line) of a text, and the remaining text after.
672    Don't stop in the middle of [Code], [CodePre], [Verbatim], [List], [Enum],
673    [Latex], [Link], [Ref], [Subscript] or [Superscript].*)
674 val first_sentence_and_rest_of_text : text -> text * text
675
676 (** Return the given [text] without any title or list. *)
677 val text_no_title_no_list : text -> text
678
679 (** [concat sep l] concats the given list of text [l], each separated with
680    the text [sep]. *)
681 val text_concat : Odoc_types.text -> Odoc_types.text list -> Odoc_types.text
682
683 (** Return the list of titles in a [text].
684    A title is a title level, an optional label and a text.*)
685 val get_titles_in_text : text -> (int * string option * text) list
686
687 (** Take a sorted list of elements, a function to get the name
688    of an element and return the list of list of elements,
689    where each list group elements beginning by the same letter.
690    Since the original list is sorted, elements whose name does not
691    begin with a letter should be in the first returned list.*)
692 val create_index_lists : 'a list -> ('a -> string) -> 'a list list
693
694 (** Take a type and remove the option top constructor. This is
695    useful when printing labels, we we then remove the top option contructor
696    for optional labels.*)
697 val remove_option : Types.type_expr -> Types.type_expr
698
699 (** Return [true] if the given label is optional.*)
700 val is_optional : string -> bool
701
702 (** Return the label name for the given label,
703    i.e. removes the beginning '?' if present.*)
704 val label_name : string -> string
705
706 (** Return the given name where the module name or
707    part of it was removed, according to the list of modules
708    which must be hidden (cf {!Odoc_args.hidden_modules})*)
709 val use_hidden_modules : Name.t -> Name.t
710
711 (** Print the given string if the verbose mode is activated. *)
712 val verbose : string -> unit
713
714 (** Print a warning message to stderr.
715    If warnings must be treated as errors, then the
716    error counter is incremented. *)
717 val warning : string -> unit
718
719 (** A flag to indicate whether ocamldoc warnings must be printed or not. *)
720 val print_warnings : bool ref
721
722 (** Increment this counter when an error is encountered.
723    The ocamldoc tool will print the number of errors
724    encountered exit with code 1 if this number is greater
725    than 0. *)
726 val errors : int ref
727
728 (** Apply a function to an optional value. *)
729 val apply_opt : ('a -> 'b) -> 'a option -> 'b option
730
731 (** Apply a function to a first value if it is
732    not different from a second value. If the two values
733    are different, return the second one.*)
734 val apply_if_equal : ('a -> 'a) -> 'a -> 'a -> 'a
735
736 (** [text_of_string s] returns the text structure from the
737    given string.
738    @raise Text_syntax if a syntax error is encountered. *)
739 val text_of_string : string -> text
740
741 (** [text_string_of_text text] returns the string representing
742    the given [text]. This string can then be parsed again
743    by {!Odoc_info.text_of_string}.*)
744 val text_string_of_text : text -> string
745
746 (** [info_of_string s] parses the given string
747    like a regular ocamldoc comment and return an
748    {!Odoc_info.info} structure.
749    @return an empty structure if there was a syntax error. TODO: change this
750 *)
751 val info_of_string : string -> info
752
753 (** [info_string_of_info info] returns the string representing
754    the given [info]. This string can then be parsed again
755    by {!Odoc_info.info_of_string}.*)
756 val info_string_of_info : info -> string
757
758 (** [info_of_comment_file file] parses the given file
759    and return an {!Odoc_info.info} structure. The content of the
760    file must have the same syntax as the content of a special comment.
761    The given module list is used for cross reference.
762    @raise Failure is the file could not be opened or there is a
763    syntax error.
764 *)
765 val info_of_comment_file : Module.t_module list -> string -> info
766
767 (** [remove_ending_newline s] returns [s] without the optional ending newline. *)
768 val remove_ending_newline : string -> string
769
770 (** Research in elements *)
771 module Search :
772     sig
773       type result_element = Odoc_search.result_element =
774           Res_module of Module.t_module
775         | Res_module_type of Module.t_module_type
776         | Res_class of Class.t_class
777         | Res_class_type of Class.t_class_type
778         | Res_value of Value.t_value
779         | Res_type of Type.t_type
780         | Res_exception of Exception.t_exception
781         | Res_attribute of Value.t_attribute
782         | Res_method of Value.t_method
783         | Res_section of string  * text
784
785       (** The type representing a research result.*)
786       type search_result = result_element list
787
788       (** Research of the elements whose name matches the given regular expression.*)
789       val search_by_name : Module.t_module list -> Str.regexp -> search_result
790
791       (** A function to search all the values in a list of modules. *)
792       val values : Module.t_module list -> Value.t_value list
793
794       (** A function to search all the exceptions in a list of modules. *)
795       val exceptions : Module.t_module list -> Exception.t_exception list
796
797       (** A function to search all the types in a list of modules. *)
798       val types : Module.t_module list -> Type.t_type list
799
800       (** A function to search all the class attributes in a list of modules. *)
801       val attributes : Module.t_module list -> Value.t_attribute list
802
803       (** A function to search all the class methods in a list of modules. *)
804       val methods : Module.t_module list -> Value.t_method list
805
806       (** A function to search all the classes in a list of modules. *)
807       val classes : Module.t_module list -> Class.t_class list
808
809       (** A function to search all the class types in a list of modules. *)
810       val class_types : Module.t_module list -> Class.t_class_type list
811
812       (** A function to search all the modules in a list of modules. *)
813       val modules : Module.t_module list -> Module.t_module list
814
815       (** A function to search all the module types in a list of modules. *)
816       val module_types : Module.t_module list -> Module.t_module_type list
817
818     end
819
820 (** Scanning of collected information *)
821 module Scan :
822   sig
823     class scanner :
824       object
825       (** Scan of 'leaf elements'. *)
826
827         method scan_value : Value.t_value -> unit
828         method scan_type : Type.t_type -> unit
829         method scan_exception : Exception.t_exception -> unit
830         method scan_attribute : Value.t_attribute -> unit
831         method scan_method : Value.t_method -> unit
832         method scan_included_module : Module.included_module -> unit
833
834       (** Scan of a class. *)
835
836         (** Scan of a comment inside a class. *)
837         method scan_class_comment : text -> unit
838
839        (** Override this method to perform controls on the class comment
840           and params. This method is called before scanning the class elements.
841           @return true if the class elements must be scanned.*)
842         method scan_class_pre : Class.t_class -> bool
843
844        (** This method scan the elements of the given class. *)
845         method scan_class_elements : Class.t_class -> unit
846
847        (** Scan of a class. Should not be overriden. It calls [scan_class_pre]
848           and if [scan_class_pre] returns [true], then it calls scan_class_elements.*)
849         method scan_class : Class.t_class -> unit
850
851       (** Scan of a class type. *)
852
853         (** Scan of a comment inside a class type. *)
854         method scan_class_type_comment : text -> unit
855
856         (** Override this method to perform controls on the class type comment
857            and form. This method is called before scanning the class type elements.
858            @return true if the class type elements must be scanned.*)
859         method scan_class_type_pre : Class.t_class_type -> bool
860
861         (** This method scan the elements of the given class type. *)
862         method scan_class_type_elements : Class.t_class_type -> unit
863
864         (** Scan of a class type. Should not be overriden. It calls [scan_class_type_pre]
865            and if [scan_class_type_pre] returns [true], then it calls scan_class_type_elements.*)
866         method scan_class_type : Class.t_class_type -> unit
867
868       (** Scan of modules. *)
869
870         (** Scan of a comment inside a module. *)
871         method scan_module_comment : text -> unit
872
873         (** Override this method to perform controls on the module comment
874            and form. This method is called before scanning the module elements.
875            @return true if the module elements must be scanned.*)
876         method scan_module_pre : Module.t_module -> bool
877
878         (** This method scan the elements of the given module. *)
879         method scan_module_elements : Module.t_module -> unit
880
881        (** Scan of a module. Should not be overriden. It calls [scan_module_pre]
882           and if [scan_module_pre] returns [true], then it calls scan_module_elements.*)
883         method scan_module : Module.t_module -> unit
884
885       (** Scan of module types. *)
886
887         (** Scan of a comment inside a module type. *)
888         method scan_module_type_comment : text -> unit
889
890         (** Override this method to perform controls on the module type comment
891            and form. This method is called before scanning the module type elements.
892            @return true if the module type elements must be scanned. *)
893         method scan_module_type_pre : Module.t_module_type -> bool
894
895         (** This method scan the elements of the given module type. *)
896         method scan_module_type_elements : Module.t_module_type -> unit
897
898         (** Scan of a module type. Should not be overriden. It calls [scan_module_type_pre]
899            and if [scan_module_type_pre] returns [true], then it calls scan_module_type_elements.*)
900         method scan_module_type : Module.t_module_type -> unit
901
902       (** Main scanning method. *)
903
904         (** Scan a list of modules. *)
905         method scan_module_list : Module.t_module list -> unit
906       end
907   end
908
909 (** Computation of dependencies. *)
910 module Dep :
911   sig
912     (** Modify the modules depencies of the given list of modules,
913        to get the minimum transitivity kernel. *)
914     val kernel_deps_of_modules : Module.t_module list -> unit
915
916     (** Return the list of dependencies between the given types,
917        in the form of a list [(type name, names of types it depends on)].
918        @param kernel indicates if we must keep only the transitivity kernel
919        of the dependencies. Default is [false].
920     *)
921     val deps_of_types : ?kernel: bool -> Type.t_type list -> (Type.t_type * (Name.t list)) list
922   end
923
924 (** {2 Command line arguments} *)
925
926 (**  You can use this module to create custom generators.*)
927 module Args :
928     sig
929       (** The kind of source file in arguments. *)
930       type source_file =
931           Impl_file of string
932         | Intf_file of string
933         | Text_file of string
934
935       (** The class type of documentation generators. *)
936       class type doc_generator =
937         object method generate : Module.t_module list -> unit end
938
939       (** The file used by the generators outputting only one file. *)
940       val out_file : string ref
941
942       (** Verbose mode or not. *)
943       val verbose : bool ref
944
945       (** The optional title to use in the generated documentation. *)
946       val title : string option ref
947
948       (** To inverse [.ml] and [.mli] files while merging comments. *)
949       val inverse_merge_ml_mli : bool ref
950
951       (** To filter module elements according to module type constraints. *)
952       val filter_with_module_constraints : bool ref
953
954       (** To keep the code while merging, when we have both .ml and .mli files for a module. *)
955       val keep_code : bool ref
956
957       (** The optional file whose content can be used as intro text. *)
958       val intro_file : string option ref
959
960       (** Flag to indicate whether we must display the complete list of parameters
961          for functions and methods. *)
962       val with_parameter_list : bool ref
963
964       (** The list of module names to hide. *)
965       val hidden_modules : string list ref
966
967       (** The directory where files have to be generated. *)
968       val target_dir : string ref
969
970       (** An optional file to use where a CSS style is defined (for HTML). *)
971       val css_style : string option ref
972
973       (** Generate only index files. (for HTML). *)
974       val index_only : bool ref
975
976       (** To colorize code in HTML generated documentation pages, not code pages. *)
977       val colorize_code : bool ref
978
979       (** To display functors in short form rather than with "functor ... -> ",
980          in HTML generated documentation. *)
981       val html_short_functors : bool ref
982
983       (** The flag which indicates if we must generate a header (for LaTeX). *)
984       val with_header : bool ref
985
986       (** The flag which indicates if we must generate a trailer (for LaTeX). *)
987       val with_trailer : bool ref
988
989       (** The flag to indicate if we must generate one file per module (for LaTeX). *)
990       val separate_files : bool ref
991
992       (** The list of pairs (title level, sectionning style). *)
993       val latex_titles : (int * string) list ref
994
995       (** The prefix to use for value labels in LaTeX. *)
996       val latex_value_prefix : string ref
997
998       (** The prefix to use for type labels in LaTeX. *)
999       val latex_type_prefix : string ref
1000
1001       (** The prefix to use for exception labels in LaTeX. *)
1002       val latex_exception_prefix : string ref
1003
1004       (** The prefix to use for module labels in LaTeX. *)
1005       val latex_module_prefix : string ref
1006
1007       (** The prefix to use for module type labels in LaTeX. *)
1008       val latex_module_type_prefix : string ref
1009
1010       (** The prefix to use for class labels in LaTeX. *)
1011       val latex_class_prefix : string ref
1012
1013       (** The prefix to use for class type labels in LaTeX. *)
1014       val latex_class_type_prefix : string ref
1015
1016       (** The prefix to use for attribute labels in LaTeX. *)
1017       val latex_attribute_prefix : string ref
1018
1019       (** The prefix to use for method labels in LaTeX. *)
1020       val latex_method_prefix : string ref
1021
1022       (** The flag which indicates if we must generate a table of contents (for LaTeX). *)
1023       val with_toc : bool ref
1024
1025       (** The flag which indicates if we must generate an index (for TeXinfo). *)
1026       val with_index : bool ref
1027
1028       (** The flag which indicates if we must escape accentuated characters (for TeXinfo).*)
1029       val esc_8bits : bool ref
1030
1031       (** The Info directory section *)
1032       val info_section : string ref
1033
1034       (** The Info directory entries to insert *)
1035       val info_entry : string list ref
1036
1037       (** Include all modules or only the ones on the command line, for the dot ouput. *)
1038       val dot_include_all : bool ref
1039
1040       (** Generate dependency graph for types. *)
1041       val dot_types : bool ref
1042
1043       (** Perform transitive reduction before dot output. *)
1044       val dot_reduce : bool ref
1045
1046       (** The colors used in the dot output. *)
1047       val dot_colors : string list ref
1048
1049       (** The suffix for man pages. *)
1050       val man_suffix : string ref
1051
1052       (** The section for man pages. *)
1053       val man_section : string ref
1054
1055       (** The flag to generate all man pages or only for modules and classes.*)
1056       val man_mini : bool ref
1057
1058       (** The files to be analysed. *)
1059       val files : source_file list ref
1060
1061       (** To set the documentation generator. *)
1062       val set_doc_generator : doc_generator option -> unit
1063
1064       (** Add an option specification. *)
1065       val add_option : string * Arg.spec * string -> unit
1066     end
1067
1068 (** Analysis of the given source files.
1069    @param init is the list of modules already known from a previous analysis.
1070    @return the list of analysed top modules. *)
1071 val analyse_files :
1072     ?merge_options:Odoc_types.merge_option list ->
1073       ?include_dirs:string list ->
1074         ?labels:bool ->
1075           ?sort_modules:bool ->
1076             ?no_stop:bool ->
1077               ?init: Odoc_module.t_module list ->
1078                 Args.source_file list ->
1079                   Module.t_module list
1080
1081 (** Dump of a list of modules into a file.
1082    @raise Failure if an error occurs.*)
1083 val dump_modules : string -> Odoc_module.t_module list -> unit
1084
1085 (** Load of a list of modules from a file.
1086    @raise Failure if an error occurs.*)
1087 val load_modules : string -> Odoc_module.t_module list