1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Typechecking of type expressions for the core language *)
|
|
|
|
|
2013-01-29 06:21:12 -08:00
|
|
|
open Types
|
2000-03-06 14:12:09 -08:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
val transl_simple_type:
|
2012-05-30 07:52:37 -07:00
|
|
|
Env.t -> bool -> Parsetree.core_type -> Typedtree.core_type
|
2002-04-18 00:27:47 -07:00
|
|
|
val transl_simple_type_univars:
|
2012-05-30 07:52:37 -07:00
|
|
|
Env.t -> Parsetree.core_type -> Typedtree.core_type
|
1997-01-20 09:11:47 -08:00
|
|
|
val transl_simple_type_delayed:
|
2012-05-30 07:52:37 -07:00
|
|
|
Env.t -> Parsetree.core_type -> Typedtree.core_type * (unit -> unit)
|
1997-01-20 09:11:47 -08:00
|
|
|
(* Translate a type, but leave type variables unbound. Returns
|
|
|
|
the type and a function that binds the type variable. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val transl_type_scheme:
|
2012-05-30 07:52:37 -07:00
|
|
|
Env.t -> Parsetree.core_type -> Typedtree.core_type
|
1995-05-04 03:15:53 -07:00
|
|
|
val reset_type_variables: unit -> unit
|
2013-04-16 00:51:27 -07:00
|
|
|
val enter_type_variable: string Location.loc -> type_expr
|
2013-01-29 06:21:12 -08:00
|
|
|
val type_variable: Location.t -> string -> type_expr
|
2002-08-04 22:58:08 -07:00
|
|
|
|
|
|
|
type variable_context
|
|
|
|
val narrow: unit -> variable_context
|
|
|
|
val widen: variable_context -> unit
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2013-04-16 00:51:27 -07:00
|
|
|
exception Already_bound of Location.t
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
type error =
|
|
|
|
Unbound_type_variable of string
|
|
|
|
| Unbound_type_constructor of Longident.t
|
2001-11-27 18:14:39 -08:00
|
|
|
| Unbound_type_constructor_2 of Path.t
|
1995-05-04 03:15:53 -07:00
|
|
|
| Type_arity_mismatch of Longident.t * int * int
|
1996-04-22 04:15:41 -07:00
|
|
|
| Bound_type_variable of string
|
|
|
|
| Recursive_type
|
|
|
|
| Unbound_row_variable of Longident.t
|
2013-01-29 06:21:12 -08:00
|
|
|
| Type_mismatch of (type_expr * type_expr) list
|
|
|
|
| Alias_type_mismatch of (type_expr * type_expr) list
|
1999-11-30 08:07:38 -08:00
|
|
|
| Present_has_conjunction of string
|
|
|
|
| Present_has_no_type of string
|
2013-01-29 06:21:12 -08:00
|
|
|
| Constructor_mismatch of type_expr * type_expr
|
|
|
|
| Not_a_variant of type_expr
|
2002-01-03 18:02:50 -08:00
|
|
|
| Variant_tags of string * string
|
2003-03-07 00:59:15 -08:00
|
|
|
| Invalid_variable_name of string
|
2013-01-29 06:21:12 -08:00
|
|
|
| Cannot_quantify of string * type_expr
|
2011-12-14 02:26:15 -08:00
|
|
|
| Multiple_constraints_on_type of Longident.t
|
2010-01-20 08:26:46 -08:00
|
|
|
| Repeated_method_label of string
|
2010-05-18 09:46:46 -07:00
|
|
|
| Unbound_value of Longident.t
|
|
|
|
| Unbound_constructor of Longident.t
|
|
|
|
| Unbound_label of Longident.t
|
|
|
|
| Unbound_module of Longident.t
|
|
|
|
| Unbound_class of Longident.t
|
2010-05-18 10:18:24 -07:00
|
|
|
| Unbound_modtype of Longident.t
|
2010-05-18 10:25:02 -07:00
|
|
|
| Unbound_cltype of Longident.t
|
2010-05-18 09:46:46 -07:00
|
|
|
| Ill_typed_functor_application of Longident.t
|
2013-04-29 08:39:00 -07:00
|
|
|
| Illegal_reference_to_recursive_module
|
2013-02-28 08:51:59 -08:00
|
|
|
| Extension of string
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2013-01-29 06:21:12 -08:00
|
|
|
exception Error of Location.t * Env.t * error
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2013-01-29 06:21:12 -08:00
|
|
|
val report_error: Env.t -> Format.formatter -> error -> unit
|
2009-10-26 03:53:16 -07:00
|
|
|
|
|
|
|
(* Support for first-class modules. *)
|
2012-05-31 01:07:31 -07:00
|
|
|
val transl_modtype_longident: (* from Typemod *)
|
|
|
|
(Location.t -> Env.t -> Longident.t -> Path.t) ref
|
|
|
|
val transl_modtype: (* from Typemod *)
|
|
|
|
(Env.t -> Parsetree.module_type -> Typedtree.module_type) ref
|
|
|
|
val create_package_mty:
|
|
|
|
Location.t -> Env.t -> Parsetree.package_type ->
|
|
|
|
(Longident.t Asttypes.loc * Parsetree.core_type) list *
|
|
|
|
Parsetree.module_type
|
2010-05-18 09:46:46 -07:00
|
|
|
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_type:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> Path.t * type_declaration
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_constructor:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> constructor_description
|
2012-10-29 00:54:06 -07:00
|
|
|
val find_all_constructors:
|
2013-09-27 08:04:03 -07:00
|
|
|
Env.t -> Location.t -> Longident.t ->
|
2013-01-29 06:21:12 -08:00
|
|
|
(constructor_description * (unit -> unit)) list
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_label:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> label_description
|
2012-10-29 00:54:06 -07:00
|
|
|
val find_all_labels:
|
2013-09-27 08:04:03 -07:00
|
|
|
Env.t -> Location.t -> Longident.t ->
|
2013-01-29 06:21:12 -08:00
|
|
|
(label_description * (unit -> unit)) list
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_value:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> Path.t * value_description
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_class:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> Path.t * class_declaration
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_module:
|
2013-09-27 10:05:39 -07:00
|
|
|
Env.t -> Location.t -> Longident.t -> Path.t * module_declaration
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_modtype:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> Path.t * modtype_declaration
|
2012-05-31 01:07:31 -07:00
|
|
|
val find_class_type:
|
2013-01-29 06:21:12 -08:00
|
|
|
Env.t -> Location.t -> Longident.t -> Path.t * class_type_declaration
|
2012-10-29 00:54:06 -07:00
|
|
|
|
2012-12-26 18:34:49 -08:00
|
|
|
val unbound_constructor_error: Env.t -> Longident.t Location.loc -> 'a
|
|
|
|
val unbound_label_error: Env.t -> Longident.t Location.loc -> 'a
|
2012-10-31 20:32:34 -07:00
|
|
|
|
|
|
|
type cd
|
|
|
|
val spellcheck_simple:
|
|
|
|
Format.formatter ->
|
|
|
|
(('a -> cd -> cd) -> Longident.t option -> 'b -> cd -> cd) ->
|
|
|
|
('a -> string) -> 'b -> Longident.t -> unit
|
2013-09-27 08:04:03 -07:00
|
|
|
|
|
|
|
val check_deprecated: Location.t -> Parsetree.attributes -> string -> unit
|
|
|
|
|