]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/typing/typedecl.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / typing / typedecl.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: typedecl.mli 9292 2009-06-08 04:08:14Z garrigue $ *)
14
15 (* Typing of type definitions and primitive definitions *)
16
17 open Types
18 open Format
19
20 val transl_type_decl:
21     Env.t -> (string * Parsetree.type_declaration) list ->
22                                   (Ident.t * type_declaration) list * Env.t
23 val transl_exception:
24     Env.t -> Parsetree.exception_declaration -> exception_declaration
25
26 val transl_exn_rebind:
27     Env.t -> Location.t -> Longident.t -> Path.t * exception_declaration
28
29 val transl_value_decl:
30     Env.t -> Parsetree.value_description -> value_description
31
32 val transl_with_constraint:
33     Env.t -> Ident.t -> Path.t option ->
34     Parsetree.type_declaration -> type_declaration
35
36 val abstract_type_decl: int -> type_declaration
37 val approx_type_decl:
38     Env.t -> (string * Parsetree.type_declaration) list ->
39                                   (Ident.t * type_declaration) list
40 val check_recmod_typedecl:
41     Env.t -> Location.t -> Ident.t list -> Path.t -> type_declaration -> unit
42
43 (* for fixed types *)
44 val is_fixed_type : Parsetree.type_declaration -> bool
45
46 (* for typeclass.ml *)
47 val compute_variance_decls:
48     Env.t ->
49     (Ident.t * type_declaration * type_declaration * class_declaration *
50        cltype_declaration * ((bool * bool) list * Location.t)) list ->
51     (type_declaration * type_declaration * class_declaration *
52        cltype_declaration) list
53     
54 type error =
55     Repeated_parameter
56   | Duplicate_constructor of string
57   | Too_many_constructors
58   | Duplicate_label of string
59   | Recursive_abbrev of string
60   | Definition_mismatch of type_expr
61   | Constraint_failed of type_expr * type_expr
62   | Unconsistent_constraint of (type_expr * type_expr) list
63   | Type_clash of (type_expr * type_expr) list
64   | Parameters_differ of Path.t * type_expr * type_expr
65   | Null_arity_external
66   | Missing_native_external
67   | Unbound_type_var of type_expr * type_declaration
68   | Unbound_exception of Longident.t
69   | Not_an_exception of Longident.t
70   | Bad_variance of int * (bool*bool) * (bool*bool)
71   | Unavailable_type_constructor of Path.t
72   | Bad_fixed_type of string
73   | Unbound_type_var_exc of type_expr * type_expr
74
75 exception Error of Location.t * error
76
77 val report_error: formatter -> error -> unit