]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/typing/types.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / typing / types.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: types.mli 8922 2008-07-19 02:13:09Z garrigue $ *)
14
15 (* Representation of types and declarations *)
16
17 open Asttypes
18
19 (* Type expressions for the core language *)
20
21 type type_expr =
22   { mutable desc: type_desc;
23     mutable level: int;
24     mutable id: int }
25
26 and type_desc =
27     Tvar
28   | Tarrow of label * type_expr * type_expr * commutable
29   | Ttuple of type_expr list
30   | Tconstr of Path.t * type_expr list * abbrev_memo ref
31   | Tobject of type_expr * (Path.t * type_expr list) option ref
32   | Tfield of string * field_kind * type_expr * type_expr
33   | Tnil
34   | Tlink of type_expr
35   | Tsubst of type_expr         (* for copying *)
36   | Tvariant of row_desc
37   | Tunivar
38   | Tpoly of type_expr * type_expr list
39
40 and row_desc =
41     { row_fields: (label * row_field) list;
42       row_more: type_expr;
43       row_bound: unit; (* kept for compatibility *)
44       row_closed: bool;
45       row_fixed: bool;
46       row_name: (Path.t * type_expr list) option }
47
48 and row_field =
49     Rpresent of type_expr option
50   | Reither of bool * type_expr list * bool * row_field option ref
51         (* 1st true denotes a constant constructor *)
52         (* 2nd true denotes a tag in a pattern matching, and
53            is erased later *)
54   | Rabsent
55
56 and abbrev_memo =
57     Mnil
58   | Mcons of private_flag * Path.t * type_expr * type_expr * abbrev_memo
59   | Mlink of abbrev_memo ref
60
61 and field_kind =
62     Fvar of field_kind option ref
63   | Fpresent
64   | Fabsent
65
66 and commutable =
67     Cok
68   | Cunknown
69   | Clink of commutable ref
70
71 module TypeOps : sig
72   type t = type_expr
73   val compare : t -> t -> int
74   val equal : t -> t -> bool
75   val hash : t -> int
76 end
77
78 (* Maps of methods and instance variables *)
79
80 module Meths : Map.S with type key = string
81 module Vars  : Map.S with type key = string
82
83 (* Value descriptions *)
84
85 type value_description =
86   { val_type: type_expr;                (* Type of the value *)
87     val_kind: value_kind }
88
89 and value_kind =
90     Val_reg                             (* Regular value *)
91   | Val_prim of Primitive.description   (* Primitive *)
92   | Val_ivar of mutable_flag * string   (* Instance variable (mutable ?) *)
93   | Val_self of (Ident.t * type_expr) Meths.t ref *
94                 (Ident.t * Asttypes.mutable_flag *
95                  Asttypes.virtual_flag * type_expr) Vars.t ref *
96                 string * type_expr
97                                         (* Self *)
98   | Val_anc of (string * Ident.t) list * string
99                                         (* Ancestor *)
100   | Val_unbound                         (* Unbound variable *)
101
102 (* Constructor descriptions *)
103
104 type constructor_description =
105   { cstr_res: type_expr;                (* Type of the result *)
106     cstr_args: type_expr list;          (* Type of the arguments *)
107     cstr_arity: int;                    (* Number of arguments *)
108     cstr_tag: constructor_tag;          (* Tag for heap blocks *)
109     cstr_consts: int;                   (* Number of constant constructors *)
110     cstr_nonconsts: int;                (* Number of non-const constructors *)
111     cstr_private: private_flag }        (* Read-only constructor? *)
112
113 and constructor_tag =
114     Cstr_constant of int                (* Constant constructor (an int) *)
115   | Cstr_block of int                   (* Regular constructor (a block) *)
116   | Cstr_exception of Path.t            (* Exception constructor *)
117
118 (* Record label descriptions *)
119
120 type label_description =
121   { lbl_res: type_expr;                 (* Type of the result *)
122     lbl_arg: type_expr;                 (* Type of the argument *)
123     lbl_mut: mutable_flag;              (* Is this a mutable field? *)
124     lbl_pos: int;                       (* Position in block *)
125     lbl_all: label_description array;   (* All the labels in this type *)
126     lbl_repres: record_representation;  (* Representation for this record *)
127     lbl_private: private_flag }         (* Read-only field? *)
128
129 and record_representation =
130     Record_regular                      (* All fields are boxed / tagged *)
131   | Record_float                        (* All fields are floats *)
132
133 (* Type definitions *)
134
135 type type_declaration =
136   { type_params: type_expr list;
137     type_arity: int;
138     type_kind: type_kind;
139     type_private: private_flag;
140     type_manifest: type_expr option;
141     type_variance: (bool * bool * bool) list }
142             (* covariant, contravariant, weakly contravariant *)
143
144 and type_kind =
145     Type_abstract
146   | Type_variant of (string * type_expr list) list
147   | Type_record of
148       (string * mutable_flag * type_expr) list * record_representation
149
150 type exception_declaration = type_expr list
151
152 (* Type expressions for the class language *)
153
154 module Concr : Set.S with type elt = string
155
156 type class_type =
157     Tcty_constr of Path.t * type_expr list * class_type
158   | Tcty_signature of class_signature
159   | Tcty_fun of label * type_expr * class_type
160
161 and class_signature =
162   { cty_self: type_expr;
163     cty_vars:
164       (Asttypes.mutable_flag * Asttypes.virtual_flag * type_expr) Vars.t;
165     cty_concr: Concr.t;
166     cty_inher: (Path.t * type_expr list) list }
167
168 type class_declaration =
169   { cty_params: type_expr list;
170     mutable cty_type: class_type;
171     cty_path: Path.t;
172     cty_new: type_expr option;
173     cty_variance: (bool * bool) list }
174
175 type cltype_declaration =
176   { clty_params: type_expr list;
177     clty_type: class_type;
178     clty_path: Path.t;
179     clty_variance: (bool * bool) list }
180
181 (* Type expressions for the module language *)
182
183 type module_type =
184     Tmty_ident of Path.t
185   | Tmty_signature of signature
186   | Tmty_functor of Ident.t * module_type * module_type
187
188 and signature = signature_item list
189
190 and signature_item =
191     Tsig_value of Ident.t * value_description
192   | Tsig_type of Ident.t * type_declaration * rec_status
193   | Tsig_exception of Ident.t * exception_declaration
194   | Tsig_module of Ident.t * module_type * rec_status
195   | Tsig_modtype of Ident.t * modtype_declaration
196   | Tsig_class of Ident.t * class_declaration * rec_status
197   | Tsig_cltype of Ident.t * cltype_declaration * rec_status
198
199 and modtype_declaration =
200     Tmodtype_abstract
201   | Tmodtype_manifest of module_type
202
203 and rec_status =
204     Trec_not                            (* not recursive *)
205   | Trec_first                          (* first in a recursive group *)
206   | Trec_next                           (* not first in a recursive group *)