Merge commit 'ocaml3102'
[ocaml.git] / typing / ctype.mli
blobffc8b872e2c6abf531e009051601e13ea14f711a
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 (***********************************************************************)
13 (* $Id$ *)
15 (* Operations on core types *)
17 open Asttypes
18 open Types
20 exception Unify of (type_expr * type_expr) list
21 exception Tags of label * label
22 exception Subtype of
23 (type_expr * type_expr) list * (type_expr * type_expr) list
24 exception Cannot_expand
25 exception Cannot_apply
26 exception Recursive_abbrev
28 val init_def: int -> unit
29 (* Set the initial variable level *)
30 val begin_def: unit -> unit
31 (* Raise the variable level by one at the beginning of a definition. *)
32 val end_def: unit -> unit
33 (* Lower the variable level by one at the end of a definition *)
34 val begin_class_def: unit -> unit
35 val raise_nongen_level: unit -> unit
36 val reset_global_level: unit -> unit
37 (* Reset the global level before typing an expression *)
38 val increase_global_level: unit -> int
39 val restore_global_level: int -> unit
40 (* This pair of functions is only used in Typetexp *)
42 val newty: type_desc -> type_expr
43 val newvar: unit -> type_expr
44 (* Return a fresh variable *)
45 val new_global_var: unit -> type_expr
46 (* Return a fresh variable, bound at toplevel
47 (as type variables ['a] in type constraints). *)
48 val newobj: type_expr -> type_expr
49 val newconstr: Path.t -> type_expr list -> type_expr
50 val none: type_expr
51 (* A dummy type expression *)
53 val repr: type_expr -> type_expr
54 (* Return the canonical representative of a type. *)
56 val dummy_method: label
57 val object_fields: type_expr -> type_expr
58 val flatten_fields:
59 type_expr -> (string * field_kind * type_expr) list * type_expr
60 (* Transform a field type into a list of pairs label-type *)
61 (* The fields are sorted *)
62 val associate_fields:
63 (string * field_kind * type_expr) list ->
64 (string * field_kind * type_expr) list ->
65 (string * field_kind * type_expr * field_kind * type_expr) list *
66 (string * field_kind * type_expr) list *
67 (string * field_kind * type_expr) list
68 val opened_object: type_expr -> bool
69 val close_object: type_expr -> unit
70 val row_variable: type_expr -> type_expr
71 (* Return the row variable of an open object type *)
72 val set_object_name:
73 Ident.t -> type_expr -> type_expr list -> type_expr -> unit
74 val remove_object_name: type_expr -> unit
75 val hide_private_methods: type_expr -> unit
76 val find_cltype_for_path: Env.t -> Path.t -> type_declaration * type_expr
78 val sort_row_fields: (label * row_field) list -> (label * row_field) list
79 val merge_row_fields:
80 (label * row_field) list -> (label * row_field) list ->
81 (label * row_field) list * (label * row_field) list *
82 (label * row_field * row_field) list
83 val filter_row_fields:
84 bool -> (label * row_field) list -> (label * row_field) list
86 val generalize: type_expr -> unit
87 (* Generalize in-place the given type *)
88 val iterative_generalization: int -> type_expr list -> type_expr list
89 (* Efficient repeated generalization of a type *)
90 val generalize_expansive: Env.t -> type_expr -> unit
91 (* Generalize the covariant part of a type, making
92 contravariant branches non-generalizable *)
93 val generalize_global: type_expr -> unit
94 (* Generalize the structure of a type, lowering variables
95 to !global_level *)
96 val generalize_structure: type_expr -> unit
97 (* Same, but variables are only lowered to !current_level *)
98 val generalize_spine: type_expr -> unit
99 (* Special function to generalize a method during inference *)
100 val correct_levels: type_expr -> type_expr
101 (* Returns a copy with decreasing levels *)
102 val limited_generalize: type_expr -> type_expr -> unit
103 (* Only generalize some part of the type
104 Make the remaining of the type non-generalizable *)
106 val instance: type_expr -> type_expr
107 (* Take an instance of a type scheme *)
108 val instance_list: type_expr list -> type_expr list
109 (* Take an instance of a list of type schemes *)
110 val instance_constructor:
111 constructor_description -> type_expr list * type_expr
112 (* Same, for a constructor *)
113 val instance_parameterized_type:
114 type_expr list -> type_expr -> type_expr list * type_expr
115 val instance_parameterized_type_2:
116 type_expr list -> type_expr list -> type_expr ->
117 type_expr list * type_expr list * type_expr
118 val instance_class:
119 type_expr list -> class_type -> type_expr list * class_type
120 val instance_poly:
121 bool -> type_expr list -> type_expr -> type_expr list * type_expr
122 (* Take an instance of a type scheme containing free univars *)
123 val instance_label:
124 bool -> label_description -> type_expr list * type_expr * type_expr
125 (* Same, for a label *)
126 val apply:
127 Env.t -> type_expr list -> type_expr -> type_expr list -> type_expr
128 (* [apply [p1...pN] t [a1...aN]] match the arguments [ai] to
129 the parameters [pi] and returns the corresponding instance of
130 [t]. Exception [Cannot_apply] is raised in case of failure. *)
132 val expand_head_once: Env.t -> type_expr -> type_expr
133 val expand_head: Env.t -> type_expr -> type_expr
134 val full_expand: Env.t -> type_expr -> type_expr
136 val enforce_constraints: Env.t -> type_expr -> unit
138 val unify: Env.t -> type_expr -> type_expr -> unit
139 (* Unify the two types given. Raise [Unify] if not possible. *)
140 val unify_var: Env.t -> type_expr -> type_expr -> unit
141 (* Same as [unify], but allow free univars when first type
142 is a variable. *)
143 val filter_arrow: Env.t -> type_expr -> label -> type_expr * type_expr
144 (* A special case of unification (with l:'a -> 'b). *)
145 val filter_method: Env.t -> string -> private_flag -> type_expr -> type_expr
146 (* A special case of unification (with {m : 'a; 'b}). *)
147 val check_filter_method: Env.t -> string -> private_flag -> type_expr -> unit
148 (* A special case of unification (with {m : 'a; 'b}), returning unit. *)
149 val deep_occur: type_expr -> type_expr -> bool
150 val filter_self_method:
151 Env.t -> string -> private_flag -> (Ident.t * type_expr) Meths.t ref ->
152 type_expr -> Ident.t * type_expr
153 val moregeneral: Env.t -> bool -> type_expr -> type_expr -> bool
154 (* Check if the first type scheme is more general than the second. *)
156 val rigidify: type_expr -> type_expr list
157 (* "Rigidify" a type and return its type variable *)
158 val all_distinct_vars: Env.t -> type_expr list -> bool
159 (* Check those types are all distinct type variables *)
160 val matches : Env.t -> type_expr -> type_expr -> bool
161 (* Same as [moregeneral false], implemented using the two above
162 functions and backtracking. Ignore levels *)
164 type class_match_failure =
165 CM_Virtual_class
166 | CM_Parameter_arity_mismatch of int * int
167 | CM_Type_parameter_mismatch of (type_expr * type_expr) list
168 | CM_Class_type_mismatch of class_type * class_type
169 | CM_Parameter_mismatch of (type_expr * type_expr) list
170 | CM_Val_type_mismatch of string * (type_expr * type_expr) list
171 | CM_Meth_type_mismatch of string * (type_expr * type_expr) list
172 | CM_Non_mutable_value of string
173 | CM_Non_concrete_value of string
174 | CM_Missing_value of string
175 | CM_Missing_method of string
176 | CM_Hide_public of string
177 | CM_Hide_virtual of string * string
178 | CM_Public_method of string
179 | CM_Private_method of string
180 | CM_Virtual_method of string
181 val match_class_types:
182 Env.t -> class_type -> class_type -> class_match_failure list
183 (* Check if the first class type is more general than the second. *)
184 val equal: Env.t -> bool -> type_expr list -> type_expr list -> bool
185 (* [equal env [x1...xn] tau [y1...yn] sigma]
186 checks whether the parameterized types
187 [/\x1.../\xn.tau] and [/\y1.../\yn.sigma] are equivalent. *)
188 val match_class_declarations:
189 Env.t -> type_expr list -> class_type -> type_expr list ->
190 class_type -> class_match_failure list
191 (* Check if the first class type is more general than the second. *)
193 val enlarge_type: Env.t -> type_expr -> type_expr * bool
194 (* Make a type larger, flag is true if some pruning had to be done *)
195 val subtype: Env.t -> type_expr -> type_expr -> unit -> unit
196 (* [subtype env t1 t2] checks that [t1] is a subtype of [t2].
197 It accumulates the constraints the type variables must
198 enforce and returns a function that inforce this
199 constraints. *)
201 val nondep_type: Env.t -> Ident.t -> type_expr -> type_expr
202 (* Return a type equivalent to the given type but without
203 references to the given module identifier. Raise [Not_found]
204 if no such type exists. *)
205 val nondep_type_decl:
206 Env.t -> Ident.t -> Ident.t -> bool -> type_declaration ->
207 type_declaration
208 (* Same for type declarations. *)
209 val nondep_class_declaration:
210 Env.t -> Ident.t -> class_declaration -> class_declaration
211 (* Same for class declarations. *)
212 val nondep_cltype_declaration:
213 Env.t -> Ident.t -> cltype_declaration -> cltype_declaration
214 (* Same for class type declarations. *)
215 val correct_abbrev: Env.t -> Path.t -> type_expr list -> type_expr -> unit
216 val cyclic_abbrev: Env.t -> Ident.t -> type_expr -> bool
217 val normalize_type: Env.t -> type_expr -> unit
219 val closed_schema: type_expr -> bool
220 (* Check whether the given type scheme contains no non-generic
221 type variables *)
223 val free_variables: type_expr -> type_expr list
224 val closed_type_decl: type_declaration -> type_expr option
225 type closed_class_failure =
226 CC_Method of type_expr * bool * string * type_expr
227 | CC_Value of type_expr * bool * string * type_expr
228 val closed_class:
229 type_expr list -> class_signature -> closed_class_failure option
230 (* Check whether all type variables are bound *)
232 val unalias: type_expr -> type_expr
233 val signature_of_class_type: class_type -> class_signature
234 val self_type: class_type -> type_expr
235 val class_type_arity: class_type -> int
236 val arity: type_expr -> int
237 (* Return the arity (as for curried functions) of the given type. *)
239 val collapse_conj_params: Env.t -> type_expr list -> unit
240 (* Collapse conjunctive types in class parameters *)