2016-02-18 07:11:59 -08:00
|
|
|
(**************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* OCaml *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. *)
|
|
|
|
(* *)
|
|
|
|
(* All rights reserved. This file is distributed under the terms of *)
|
|
|
|
(* the GNU Lesser General Public License version 2.1, with the *)
|
|
|
|
(* special exception on linking described in the file LICENSE. *)
|
|
|
|
(* *)
|
|
|
|
(**************************************************************************)
|
1995-08-09 08:06:35 -07:00
|
|
|
|
1995-07-25 04:40:07 -07:00
|
|
|
(* Typing of type definitions and primitive definitions *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-09-23 04:33:27 -07:00
|
|
|
open Types
|
2000-03-06 14:12:09 -08:00
|
|
|
open Format
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val transl_type_decl:
|
2015-03-13 04:08:30 -07:00
|
|
|
Env.t -> Asttypes.rec_flag -> Parsetree.type_declaration list ->
|
2013-03-25 11:20:11 -07:00
|
|
|
Typedtree.type_declaration list * Env.t
|
2012-05-31 01:07:31 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
val transl_exception:
|
2018-04-06 11:28:02 -07:00
|
|
|
Env.t -> Parsetree.extension_constructor ->
|
|
|
|
Typedtree.extension_constructor * Env.t
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2018-04-06 10:02:46 -07:00
|
|
|
val transl_type_exception:
|
|
|
|
Env.t ->
|
|
|
|
Parsetree.type_exception -> Typedtree.type_exception * Env.t
|
|
|
|
|
2014-05-04 16:08:45 -07:00
|
|
|
val transl_type_extension:
|
|
|
|
bool -> Env.t -> Location.t -> Parsetree.type_extension ->
|
|
|
|
Typedtree.type_extension * Env.t
|
2000-03-12 05:10:29 -08:00
|
|
|
|
1995-07-25 04:40:07 -07:00
|
|
|
val transl_value_decl:
|
2012-05-31 01:07:31 -07:00
|
|
|
Env.t -> Location.t ->
|
2013-03-25 11:04:40 -07:00
|
|
|
Parsetree.value_description -> Typedtree.value_description * Env.t
|
1995-09-28 03:42:38 -07:00
|
|
|
|
2012-05-31 01:07:31 -07:00
|
|
|
val transl_with_constraint:
|
2020-06-01 23:27:36 -07:00
|
|
|
Ident.t -> Path.t option ->
|
|
|
|
sig_env:Env.t -> sig_decl:Types.type_declaration ->
|
|
|
|
outer_env:Env.t -> Parsetree.type_declaration ->
|
|
|
|
Typedtree.type_declaration
|
2000-09-06 03:21:07 -07:00
|
|
|
|
2003-06-19 08:53:53 -07:00
|
|
|
val abstract_type_decl: int -> type_declaration
|
|
|
|
val approx_type_decl:
|
2016-03-09 02:40:16 -08:00
|
|
|
Parsetree.type_declaration list ->
|
2003-06-19 08:53:53 -07:00
|
|
|
(Ident.t * type_declaration) list
|
2003-07-01 06:05:43 -07:00
|
|
|
val check_recmod_typedecl:
|
|
|
|
Env.t -> Location.t -> Ident.t list -> Path.t -> type_declaration -> unit
|
2013-05-03 07:40:11 -07:00
|
|
|
val check_coherence:
|
2019-04-18 18:57:55 -07:00
|
|
|
Env.t -> Location.t -> Path.t -> type_declaration -> unit
|
2003-06-19 08:53:53 -07:00
|
|
|
|
2007-10-09 03:29:37 -07:00
|
|
|
(* for fixed types *)
|
|
|
|
val is_fixed_type : Parsetree.type_declaration -> bool
|
|
|
|
|
2016-05-25 07:29:05 -07:00
|
|
|
(* for typeopt.ml *)
|
|
|
|
val get_unboxed_type_representation: Env.t -> type_expr -> type_expr option
|
|
|
|
|
2015-08-25 09:18:46 -07:00
|
|
|
type native_repr_kind = Unboxed | Untagged
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
type error =
|
|
|
|
Repeated_parameter
|
|
|
|
| Duplicate_constructor of string
|
1995-05-22 08:43:44 -07:00
|
|
|
| Too_many_constructors
|
1995-05-04 03:15:53 -07:00
|
|
|
| Duplicate_label of string
|
|
|
|
| Recursive_abbrev of string
|
2014-08-22 06:45:02 -07:00
|
|
|
| Cycle_in_def of string * type_expr
|
2018-08-08 09:07:53 -07:00
|
|
|
| Definition_mismatch of type_expr * Includecore.type_mismatch option
|
2000-05-24 01:19:02 -07:00
|
|
|
| Constraint_failed of type_expr * type_expr
|
2018-09-10 13:15:45 -07:00
|
|
|
| Inconsistent_constraint of Env.t * Ctype.Unification_trace.t
|
|
|
|
| Type_clash of Env.t * Ctype.Unification_trace.t
|
2019-10-28 07:48:34 -07:00
|
|
|
| Non_regular of {
|
|
|
|
definition: Path.t;
|
|
|
|
used_as: type_expr;
|
|
|
|
defined_as: type_expr;
|
|
|
|
expansions: (type_expr * type_expr) list;
|
|
|
|
}
|
1997-05-13 07:07:00 -07:00
|
|
|
| Null_arity_external
|
2000-06-05 05:18:30 -07:00
|
|
|
| Missing_native_external
|
2005-08-13 13:59:37 -07:00
|
|
|
| Unbound_type_var of type_expr * type_declaration
|
2017-07-20 08:33:41 -07:00
|
|
|
| Cannot_extend_private_type of Path.t
|
2014-05-04 16:08:45 -07:00
|
|
|
| Not_extensible_type of Path.t
|
2018-08-08 09:07:53 -07:00
|
|
|
| Extension_mismatch of Path.t * Includecore.type_mismatch
|
2018-09-10 13:15:45 -07:00
|
|
|
| Rebind_wrong_type of Longident.t * Env.t * Ctype.Unification_trace.t
|
2014-05-04 16:08:45 -07:00
|
|
|
| Rebind_mismatch of Longident.t * Path.t * Path.t
|
|
|
|
| Rebind_private of Longident.t
|
2018-11-20 07:10:19 -08:00
|
|
|
| Variance of Typedecl_variance.error
|
2001-09-28 15:55:27 -07:00
|
|
|
| Unavailable_type_constructor of Path.t
|
2005-03-22 19:08:37 -08:00
|
|
|
| Bad_fixed_type of string
|
2014-05-04 16:08:45 -07:00
|
|
|
| Unbound_type_var_ext of type_expr * extension_constructor
|
2014-12-10 05:37:50 -08:00
|
|
|
| Val_in_structure
|
2015-08-25 09:18:46 -07:00
|
|
|
| Multiple_native_repr_attributes
|
|
|
|
| Cannot_unbox_or_untag_type of native_repr_kind
|
2016-01-18 09:34:02 -08:00
|
|
|
| Deep_unbox_or_untag_attribute of native_repr_kind
|
2018-11-20 07:28:15 -08:00
|
|
|
| Immediacy of Typedecl_immediacy.error
|
2018-12-13 21:24:44 -08:00
|
|
|
| Separability of Typedecl_separability.error
|
2016-05-25 07:29:05 -07:00
|
|
|
| Bad_unboxed_attribute of string
|
|
|
|
| Boxed_and_unboxed
|
2017-03-15 16:34:10 -07:00
|
|
|
| Nonrec_gadt
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
exception Error of Location.t * error
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
val report_error: formatter -> error -> unit
|