1995-08-09 08:06:35 -07:00
(* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *)
(* *)
1996-04-30 07:53:58 -07:00
(* Objective Caml *)
1995-08-09 08:06:35 -07:00
(* *)
1997-02-20 12:39:02 -08:00
(* Xavier Leroy and Jerome Vouillon, projet Cristal, INRIA Rocquencourt *)
1995-08-09 08:06:35 -07:00
(* *)
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
(* *)
(* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *)
(* $Id$ *)
1997-02-20 12:39:02 -08:00
(* * * * Typing of type definitions * * * *)
1995-05-04 03:15:53 -07:00
1997-02-20 12:39:02 -08:00
open Misc
2000-09-06 03:21:07 -07:00
open Asttypes
1995-05-04 03:15:53 -07:00
open Parsetree
2000-06-05 05:18:30 -07:00
open Primitive
1996-09-23 04:33:27 -07:00
open Types
1995-05-04 03:15:53 -07:00
open Typedtree
open Typetexp
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
2010-05-20 20:36:52 -07:00
| Definition_mismatch of type_expr * Includecore . type_mismatch list
2000-05-24 01:06:33 -07:00
| Constraint_failed of type_expr * type_expr
2001-12-25 19:43:41 -08:00
| Unconsistent_constraint of ( type_expr * type_expr ) list
1997-02-20 12:39:02 -08:00
| Type_clash of ( type_expr * type_expr ) list
2003-07-01 06:05:43 -07:00
| Parameters_differ of Path . t * type_expr * type_expr
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
2000-03-12 05:10:29 -08:00
| Unbound_exception of Longident . t
| Not_an_exception of Longident . t
2007-10-09 03:29:37 -07:00
| Bad_variance of int * ( bool * bool ) * ( bool * bool )
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
2009-07-20 04:51:50 -07:00
| Unbound_type_var_exc of type_expr * type_expr
1995-05-04 03:15:53 -07:00
exception Error of Location . t * error
(* Enter all declared types in the environment as abstract types *)
2000-05-23 23:19:39 -07:00
let enter_type env ( name , sdecl ) id =
let decl =
{ type_params =
List . map ( fun _ -> Btype . newgenvar () ) sdecl . ptype_params ;
type_arity = List . length sdecl . ptype_params ;
type_kind = Type_abstract ;
2007-10-09 03:29:37 -07:00
type_private = sdecl . ptype_private ;
2000-08-03 20:29:42 -07:00
type_manifest =
2000-09-06 03:21:07 -07:00
begin match sdecl . ptype_manifest with None -> None
| Some _ -> Some ( Ctype . newvar () ) end ;
2003-05-21 02:04:54 -07:00
type_variance = List . map ( fun _ -> true , true , true ) sdecl . ptype_params ;
2000-09-06 03:21:07 -07:00
}
2000-05-23 23:19:39 -07:00
in
Env . add_type id decl env
1995-05-04 03:15:53 -07:00
2000-08-03 20:29:42 -07:00
let update_type temp_env env id loc =
let path = Path . Pident id in
let decl = Env . find_type path temp_env in
match decl . type_manifest with None -> ()
| Some ty ->
let params = List . map ( fun _ -> Ctype . newvar () ) decl . type_params in
try Ctype . unify env ( Ctype . newconstr path params ) ty
with Ctype . Unify trace ->
raise ( Error ( loc , Type_clash trace ) )
2000-03-21 06:43:25 -08:00
(* Determine if a type is ( an abbreviation for ) the type "float" *)
2007-11-28 14:30:25 -08:00
(* We use the Ctype.expand_head_opt version of expand_head to get access
to the manifest type of private abbreviations . * )
2000-03-21 06:43:25 -08:00
let is_float env ty =
2007-11-28 14:30:25 -08:00
match Ctype . repr ( Ctype . expand_head_opt env ty ) with
2000-03-21 06:43:25 -08:00
{ desc = Tconstr ( p , _ , _ ) } -> Path . same p Predef . path_float
| _ -> false
2007-10-09 03:29:37 -07:00
(* Determine if a type definition defines a fixed type. ( PW ) *)
let is_fixed_type sd =
( match sd . ptype_manifest with
2008-07-17 19:17:54 -07:00
| Some { ptyp_desc =
( Ptyp_variant _ | Ptyp_object _ | Ptyp_class _ | Ptyp_alias
( { ptyp_desc = Ptyp_variant _ | Ptyp_object _ | Ptyp_class _ } , _ ) ) } -> true
2007-10-09 03:29:37 -07:00
| _ -> false ) &&
sd . ptype_kind = Ptype_abstract &&
sd . ptype_private = Private
2005-03-22 19:08:37 -08:00
(* Set the row variable in a fixed type *)
let set_fixed_row env loc p decl =
let tm =
match decl . type_manifest with
None -> assert false
| Some t -> Ctype . expand_head env t
in
let rv =
match tm . desc with
Tvariant row ->
2005-07-12 16:50:45 -07:00
let row = Btype . row_repr row in
2005-08-13 13:59:37 -07:00
tm . desc <- Tvariant { row with row_fixed = true } ;
if Btype . static_row row then Btype . newgenty Tnil
2005-07-12 16:50:45 -07:00
else row . row_more
2005-03-22 19:08:37 -08:00
| Tobject ( ty , _ ) ->
2005-08-13 13:59:37 -07:00
snd ( Ctype . flatten_fields ty )
2005-03-22 19:08:37 -08:00
| _ ->
raise ( Error ( loc , Bad_fixed_type " is not an object or variant " ) )
in
if rv . desc < > Tvar then
raise ( Error ( loc , Bad_fixed_type " has no row variable " ) ) ;
rv . desc <- Tconstr ( p , decl . type_params , ref Mnil )
1995-05-04 03:15:53 -07:00
(* Translate one type declaration *)
1995-05-30 06:36:40 -07:00
module StringSet =
Set . Make ( struct
type t = string
let compare = compare
end )
2010-09-18 21:55:40 -07:00
2000-05-23 23:19:39 -07:00
let transl_declaration env ( name , sdecl ) id =
1997-04-24 06:41:16 -07:00
(* Bind type parameters *)
reset_type_variables () ;
2002-04-18 00:27:47 -07:00
Ctype . begin_def () ;
2000-05-24 01:06:33 -07:00
let params =
2003-03-07 00:59:15 -08:00
try List . map ( enter_type_variable true sdecl . ptype_loc ) sdecl . ptype_params
2000-05-24 01:06:33 -07:00
with Already_bound ->
raise ( Error ( sdecl . ptype_loc , Repeated_parameter ) )
in
2002-04-18 00:27:47 -07:00
let cstrs = List . map
( fun ( sty , sty' , loc ) ->
transl_simple_type env false sty ,
transl_simple_type env false sty' , loc )
sdecl . ptype_cstrs
in
2000-05-23 23:19:39 -07:00
let decl =
1997-04-24 06:41:16 -07:00
{ type_params = params ;
2000-05-23 23:19:39 -07:00
type_arity = List . length params ;
1995-09-26 13:23:29 -07:00
type_kind =
2003-07-02 02:14:35 -07:00
begin match sdecl . ptype_kind with
2007-10-09 03:29:37 -07:00
Ptype_abstract -> Type_abstract
| Ptype_variant cstrs ->
1995-09-26 13:23:29 -07:00
let all_constrs = ref StringSet . empty in
List . iter
2010-09-12 22:28:30 -07:00
( fun ( name , _ , _ , loc ) ->
1995-09-26 13:23:29 -07:00
if StringSet . mem name ! all_constrs then
raise ( Error ( sdecl . ptype_loc , Duplicate_constructor name ) ) ;
all_constrs := StringSet . add name ! all_constrs )
cstrs ;
2010-09-18 21:55:40 -07:00
2010-09-12 22:28:30 -07:00
if List . length ( List . filter ( fun ( _ , args , _ , _ ) -> args < > [] ) cstrs ) (* GAH: MIGHT BE WRONG *)
2002-01-20 09:29:18 -08:00
> ( Config . max_tag + 1 ) then
1995-09-26 13:23:29 -07:00
raise ( Error ( sdecl . ptype_loc , Too_many_constructors ) ) ;
2010-09-18 21:55:40 -07:00
(* if List.for_all ( fun ( _,_,x,_ ) -> match x with Some _ -> false | None -> true ) cstrs then
2007-10-09 03:29:37 -07:00
Type_variant
( List . map
2010-09-12 22:28:30 -07:00
( fun ( name , args , _ , loc ) ->
2007-10-09 03:29:37 -07:00
( name , List . map ( transl_simple_type env true ) args ) )
cstrs )
2010-09-18 21:55:40 -07:00
else * )
let ret =
2010-09-12 23:18:22 -07:00
Type_generalized_variant
( List . map
( fun ( name , args , ret_type_opt , loc ) ->
2010-09-18 21:55:40 -07:00
let gadt =
match ret_type_opt with
| None -> None
| Some _ -> Some ( ref [] )
in
( name , List . map ( transl_simple_type ~ gadt env false ) args , may_map ( transl_simple_type ~ gadt env false ) ret_type_opt ) ) (* GAH: calling transl_simple_type with fixed=false, ask garrigue if this is ok *)
2010-09-12 23:18:22 -07:00
cstrs )
2010-09-18 21:55:40 -07:00
in
ret
2007-10-09 03:29:37 -07:00
| Ptype_record lbls ->
1995-09-26 13:23:29 -07:00
let all_labels = ref StringSet . empty in
List . iter
2004-10-06 06:06:11 -07:00
( fun ( name , mut , arg , loc ) ->
1995-09-26 13:23:29 -07:00
if StringSet . mem name ! all_labels then
raise ( Error ( sdecl . ptype_loc , Duplicate_label name ) ) ;
all_labels := StringSet . add name ! all_labels )
lbls ;
2000-03-21 06:43:25 -08:00
let lbls' =
List . map
2004-10-06 06:06:11 -07:00
( fun ( name , mut , arg , loc ) ->
2002-04-18 00:27:47 -07:00
let ty = transl_simple_type env true arg in
name , mut , match ty . desc with Tpoly ( t , [] ) -> t | _ -> ty )
2000-03-21 06:43:25 -08:00
lbls in
let rep =
if List . for_all ( fun ( name , mut , arg ) -> is_float env arg ) lbls'
then Record_float
else Record_regular in
2007-10-09 03:29:37 -07:00
Type_record ( lbls' , rep )
2003-07-02 02:14:35 -07:00
end ;
2007-10-09 03:29:37 -07:00
type_private = sdecl . ptype_private ;
2000-05-23 23:19:39 -07:00
type_manifest =
begin match sdecl . ptype_manifest with
None -> None
| Some sty ->
2007-10-09 03:29:37 -07:00
let no_row = not ( is_fixed_type sdecl ) in
2010-01-20 08:26:46 -08:00
Some ( transl_simple_type env no_row sty )
2000-09-06 03:21:07 -07:00
end ;
2003-05-21 02:04:54 -07:00
type_variance = List . map ( fun _ -> true , true , true ) params ;
2000-09-06 03:21:07 -07:00
} in
2000-05-23 23:19:39 -07:00
2010-09-18 21:55:40 -07:00
2000-05-23 23:19:39 -07:00
(* Check constraints *)
List . iter
2002-04-18 00:27:47 -07:00
( fun ( ty , ty' , loc ) ->
try Ctype . unify env ty ty' with Ctype . Unify tr ->
raise ( Error ( loc , Unconsistent_constraint tr ) ) )
cstrs ;
Ctype . end_def () ;
2010-01-20 08:26:46 -08:00
(* Add abstract row *)
2007-10-09 03:29:37 -07:00
if is_fixed_type sdecl then begin
2005-03-22 19:08:37 -08:00
let ( p , _ ) =
try Env . lookup_type ( Longident . Lident ( Ident . name id ^ " #row " ) ) env
with Not_found -> assert false in
set_fixed_row env sdecl . ptype_loc p decl
end ;
2010-01-20 08:26:46 -08:00
(* Check for cyclic abbreviations *)
begin match decl . type_manifest with None -> ()
| Some ty ->
if Ctype . cyclic_abbrev env id ty then
raise ( Error ( sdecl . ptype_loc , Recursive_abbrev name ) ) ;
end ;
2000-09-07 03:57:32 -07:00
( id , decl )
1997-02-20 12:39:02 -08:00
(* Generalize a type declaration *)
let generalize_decl decl =
List . iter Ctype . generalize decl . type_params ;
2003-07-02 02:14:35 -07:00
begin match decl . type_kind with
Type_abstract ->
1996-04-22 04:15:41 -07:00
()
2007-10-09 03:29:37 -07:00
| Type_variant v ->
2010-09-12 22:28:30 -07:00
List . iter ( fun ( _ , tyl ) -> List . iter Ctype . generalize tyl ) v (* GAH: almost sure this is wrong *)
| Type_generalized_variant v ->
List . iter ( fun ( _ , tyl , ret_type_opt ) -> List . iter Ctype . generalize tyl ; may Ctype . generalize ret_type_opt ) v (* GAH: almost sure this is wrong *)
2007-10-09 03:29:37 -07:00
| Type_record ( r , rep ) ->
1996-04-22 04:15:41 -07:00
List . iter ( fun ( _ , _ , ty ) -> Ctype . generalize ty ) r
2003-07-02 02:14:35 -07:00
end ;
1996-04-22 04:15:41 -07:00
begin match decl . type_manifest with
2003-05-01 15:22:37 -07:00
| None -> ()
1996-04-22 04:15:41 -07:00
| Some ty -> Ctype . generalize ty
1997-02-20 12:39:02 -08:00
end
2000-05-23 23:19:39 -07:00
(* Check that all constraints are enforced *)
2000-05-24 01:06:33 -07:00
module TypeSet =
Set . Make
( struct
type t = type_expr
let compare t1 t2 = t1 . id - t2 . id
end )
2003-06-28 03:46:32 -07:00
let rec check_constraints_rec env loc visited ty =
2010-09-18 21:55:40 -07:00
2000-05-23 23:19:39 -07:00
let ty = Ctype . repr ty in
2000-05-24 01:06:33 -07:00
if TypeSet . mem ty ! visited then () else begin
visited := TypeSet . add ty ! visited ;
2000-05-23 23:19:39 -07:00
match ty . desc with
| Tconstr ( path , args , _ ) ->
let args' = List . map ( fun _ -> Ctype . newvar () ) args in
2000-05-24 19:09:13 -07:00
let ty' = Ctype . newconstr path args' in
2003-06-28 03:46:32 -07:00
begin try Ctype . enforce_constraints env ty'
2000-05-23 23:19:39 -07:00
with Ctype . Unify _ -> assert false
2001-09-28 15:55:27 -07:00
| Not_found -> raise ( Error ( loc , Unavailable_type_constructor path ) )
2000-05-23 23:19:39 -07:00
end ;
2003-06-30 01:04:42 -07:00
if not ( Ctype . matches env ty ty' ) then
raise ( Error ( loc , Constraint_failed ( ty , ty' ) ) ) ;
2003-06-28 03:46:32 -07:00
List . iter ( check_constraints_rec env loc visited ) args
2002-04-18 00:27:47 -07:00
| Tpoly ( ty , tl ) ->
let _ , ty = Ctype . instance_poly false tl ty in
2003-06-28 03:46:32 -07:00
check_constraints_rec env loc visited ty
2000-05-23 23:19:39 -07:00
| _ ->
2003-06-28 03:46:32 -07:00
Btype . iter_type_expr ( check_constraints_rec env loc visited ) ty
2000-05-24 01:06:33 -07:00
end
2000-05-23 23:19:39 -07:00
2003-06-28 03:46:32 -07:00
let check_constraints env ( _ , sdecl ) ( _ , decl ) =
2000-05-24 01:06:33 -07:00
let visited = ref TypeSet . empty in
2010-09-12 22:28:30 -07:00
let process_variants l =
2003-02-27 22:59:19 -08:00
let rec find_pl = function
2007-10-09 03:29:37 -07:00
Ptype_variant pl -> pl
| Ptype_record _ | Ptype_abstract -> assert false
2000-05-23 23:19:39 -07:00
in
2003-02-27 22:59:19 -08:00
let pl = find_pl sdecl . ptype_kind in
2000-05-23 23:19:39 -07:00
List . iter
2010-09-12 22:28:30 -07:00
( fun ( name , tyl , ret_type_opt ) -> (* GAH: again, no idea *)
let styl , sret_type_opt =
2010-09-18 21:55:40 -07:00
try let ( _ , sty , sret_type_opt (* added by me *) , _ ) = List . find ( fun ( n , _ , _ , _ ) -> n = name ) pl in sty , sret_type_opt (* GAH: lord, I have no idea what this is about *)
2004-10-06 06:06:11 -07:00
with Not_found -> assert false in
2000-05-23 23:19:39 -07:00
List . iter2
2003-05-12 03:59:18 -07:00
( fun sty ty ->
2003-06-28 03:46:32 -07:00
check_constraints_rec env sty . ptyp_loc visited ty )
2010-09-12 22:28:30 -07:00
styl tyl ;
2010-09-18 21:55:40 -07:00
(* GAH : ask garrigue how to do the following: *)
2010-09-12 22:28:30 -07:00
match sret_type_opt , ret_type_opt with
| Some sr , Some r ->
check_constraints_rec env sr . ptyp_loc visited r
| _ ->
2010-09-18 21:55:40 -07:00
() )
2010-09-12 22:28:30 -07:00
l
in
begin match decl . type_kind with
| Type_abstract -> ()
| Type_variant l ->
let gen_variants lst = List . map ( fun ( a , b ) -> ( a , b , None ) ) lst in
process_variants ( gen_variants l )
| Type_generalized_variant l ->
process_variants l
2007-10-09 03:29:37 -07:00
| Type_record ( l , _ ) ->
2003-02-27 22:59:19 -08:00
let rec find_pl = function
2007-10-09 03:29:37 -07:00
Ptype_record pl -> pl
| Ptype_variant _ | Ptype_abstract -> assert false
2000-05-23 23:19:39 -07:00
in
2003-02-27 22:59:19 -08:00
let pl = find_pl sdecl . ptype_kind in
2000-05-23 23:19:39 -07:00
let rec get_loc name = function
[] -> assert false
2004-10-06 06:06:11 -07:00
| ( name' , _ , sty , _ ) :: tl ->
2000-05-23 23:19:39 -07:00
if name = name' then sty . ptyp_loc else get_loc name tl
in
List . iter
2000-05-24 01:06:33 -07:00
( fun ( name , _ , ty ) ->
2003-06-28 03:46:32 -07:00
check_constraints_rec env ( get_loc name pl ) visited ty )
2000-05-23 23:19:39 -07:00
l
2003-07-02 02:14:35 -07:00
end ;
2000-05-23 23:19:39 -07:00
begin match decl . type_manifest with
| None -> ()
| Some ty ->
let sty =
match sdecl . ptype_manifest with Some sty -> sty | _ -> assert false
in
2003-06-28 03:46:32 -07:00
check_constraints_rec env sty . ptyp_loc visited ty
2000-05-23 23:19:39 -07:00
end
1997-02-20 12:39:02 -08:00
(*
If both a variant / record definition and a type equation are given ,
need to check that the equation refers to a type of the same kind
with the same constructors and labels .
* )
let check_abbrev env ( _ , sdecl ) ( id , decl ) =
match decl with
1995-11-03 05:23:03 -08:00
{ type_kind = ( Type_variant _ | Type_record _ ) ; type_manifest = Some ty } ->
1997-02-20 12:39:02 -08:00
begin match ( Ctype . repr ty ) . desc with
1996-04-22 04:15:41 -07:00
Tconstr ( path , args , _ ) ->
1995-11-03 05:23:03 -08:00
begin try
let decl' = Env . find_type path env in
2010-05-20 20:36:52 -07:00
let err =
if List . length args < > List . length decl . type_params
then [ Includecore . Arity ]
else if not ( Ctype . equal env false args decl . type_params )
then [ Includecore . Constraint ]
else
Includecore . type_declarations env id
decl'
( Subst . type_declaration
( Subst . add_type id path Subst . identity ) decl )
in
if err < > [] then
raise ( Error ( sdecl . ptype_loc , Definition_mismatch ( ty , err ) ) )
1995-11-03 05:23:03 -08:00
with Not_found ->
2001-09-28 15:55:27 -07:00
raise ( Error ( sdecl . ptype_loc , Unavailable_type_constructor path ) )
1995-11-03 05:23:03 -08:00
end
2010-05-20 20:36:52 -07:00
| _ -> raise ( Error ( sdecl . ptype_loc , Definition_mismatch ( ty , [] ) ) )
1995-11-03 05:23:03 -08:00
end
| _ -> ()
1995-05-04 03:15:53 -07:00
1996-04-22 04:15:41 -07:00
(* Check for ill-defined abbrevs *)
1995-05-04 03:15:53 -07:00
2003-07-03 03:00:53 -07:00
let check_recursion env loc path decl to_check =
(* to_check is true for potentially mutually recursive paths.
( path , decl ) is the type declaration to be checked . * )
1995-05-04 03:15:53 -07:00
2003-07-03 03:00:53 -07:00
let visited = ref [] in
2000-05-24 19:09:13 -07:00
2003-07-03 03:00:53 -07:00
let rec check_regular cpath args prev_exp ty =
let ty = Ctype . repr ty in
if not ( List . memq ty ! visited ) then begin
visited := ty :: ! visited ;
match ty . desc with
| Tconstr ( path' , args' , _ ) ->
if Path . same path path' then begin
if not ( Ctype . equal env false args args' ) then
2005-08-13 13:59:37 -07:00
raise ( Error ( loc ,
2003-07-03 03:00:53 -07:00
Parameters_differ ( cpath , ty , Ctype . newconstr path args ) ) )
end
(* Attempt to expand a type abbreviation if:
2003-07-03 07:35:35 -07:00
1 - [ to_check path' ] holds
( otherwise the expansion cannot involve [ path ] ) ;
2003-07-03 03:00:53 -07:00
2 - we haven't expanded this type constructor before
2005-08-13 13:59:37 -07:00
( otherwise we could loop if [ path' ] is itself
2003-07-03 03:00:53 -07:00
a non - regular abbreviation ) . * )
else if to_check path' && not ( List . mem path' prev_exp ) then begin
try
(* Attempt expansion *)
2003-11-06 16:19:08 -08:00
let ( params0 , body0 ) = Env . find_type_expansion path' env in
2005-08-13 13:59:37 -07:00
let ( params , body ) =
2003-11-06 16:19:08 -08:00
Ctype . instance_parameterized_type params0 body0 in
2003-07-03 03:00:53 -07:00
begin
try List . iter2 ( Ctype . unify env ) params args'
2003-11-06 16:19:08 -08:00
with Ctype . Unify _ ->
raise ( Error ( loc , Constraint_failed
( ty , Ctype . newconstr path' params0 ) ) ) ;
2003-07-03 03:00:53 -07:00
end ;
check_regular path' args ( path' :: prev_exp ) body
with Not_found -> ()
2001-01-08 16:18:52 -08:00
end ;
2003-07-03 03:00:53 -07:00
List . iter ( check_regular cpath args prev_exp ) args'
| Tpoly ( ty , tl ) ->
let ( _ , ty ) = Ctype . instance_poly false tl ty in
check_regular cpath args prev_exp ty
| _ ->
Btype . iter_type_expr ( check_regular cpath args prev_exp ) ty
end in
2000-05-24 19:09:13 -07:00
match decl . type_manifest with
| None -> ()
| Some body ->
2003-07-03 03:00:53 -07:00
(* Check that recursion is well-founded *)
begin try
Ctype . correct_abbrev env path decl . type_params body
with Ctype . Recursive_abbrev ->
raise ( Error ( loc , Recursive_abbrev ( Path . name path ) ) )
2007-10-08 07:19:34 -07:00
| Ctype . Unify trace -> raise ( Error ( loc , Type_clash trace ) )
2003-07-03 03:00:53 -07:00
end ;
(* Check that recursion is regular *)
if decl . type_params = [] then () else
2000-05-24 19:09:13 -07:00
let ( args , body ) =
Ctype . instance_parameterized_type decl . type_params body in
2003-07-03 03:00:53 -07:00
check_regular path args [] body
let check_abbrev_recursion env id_loc_list ( id , decl ) =
check_recursion env ( List . assoc id id_loc_list ) ( Path . Pident id ) decl
( function Path . Pident id -> List . mem_assoc id id_loc_list | _ -> false )
2000-05-24 19:09:13 -07:00
2000-09-06 03:21:07 -07:00
(* Compute variance *)
2003-07-03 03:00:53 -07:00
2003-05-21 02:04:54 -07:00
let compute_variance env tvl nega posi cntr ty =
2000-09-06 03:21:07 -07:00
let pvisited = ref TypeSet . empty
2003-05-21 02:04:54 -07:00
and nvisited = ref TypeSet . empty
and cvisited = ref TypeSet . empty in
let rec compute_variance_rec posi nega cntr ty =
2000-09-06 03:21:07 -07:00
let ty = Ctype . repr ty in
if ( not posi | | TypeSet . mem ty ! pvisited )
2003-05-21 02:04:54 -07:00
&& ( not nega | | TypeSet . mem ty ! nvisited )
&& ( not cntr | | TypeSet . mem ty ! cvisited ) then
2000-09-06 03:21:07 -07:00
()
else begin
if posi then pvisited := TypeSet . add ty ! pvisited ;
if nega then nvisited := TypeSet . add ty ! nvisited ;
2003-05-21 02:04:54 -07:00
if cntr then cvisited := TypeSet . add ty ! cvisited ;
let compute_same = compute_variance_rec posi nega cntr in
2000-09-06 03:21:07 -07:00
match ty . desc with
2001-04-19 01:34:21 -07:00
Tarrow ( _ , ty1 , ty2 , _ ) ->
2003-05-21 02:04:54 -07:00
compute_variance_rec nega posi true ty1 ;
compute_same ty2
2000-09-06 03:21:07 -07:00
| Ttuple tl ->
2003-05-21 02:04:54 -07:00
List . iter compute_same tl
2000-09-06 03:21:07 -07:00
| Tconstr ( path , tl , _ ) ->
2001-09-28 15:55:27 -07:00
if tl = [] then () else begin
try
let decl = Env . find_type path env in
List . iter2
2003-05-21 02:04:54 -07:00
( fun ty ( co , cn , ct ) ->
2001-09-28 15:55:27 -07:00
compute_variance_rec
( posi && co | | nega && cn )
( posi && cn | | nega && co )
2005-08-13 13:59:37 -07:00
( cntr | | ct )
2001-09-28 15:55:27 -07:00
ty )
tl decl . type_variance
with Not_found ->
2003-05-21 02:04:54 -07:00
List . iter ( compute_variance_rec true true true ) tl
2001-09-28 15:55:27 -07:00
end
2000-09-06 03:21:07 -07:00
| Tobject ( ty , _ ) ->
2003-05-21 02:04:54 -07:00
compute_same ty
2000-09-06 03:21:07 -07:00
| Tfield ( _ , _ , ty1 , ty2 ) ->
2003-05-21 02:04:54 -07:00
compute_same ty1 ;
compute_same ty2
2000-09-06 03:21:07 -07:00
| Tsubst ty ->
2003-05-21 02:04:54 -07:00
compute_same ty
2000-09-06 03:21:07 -07:00
| Tvariant row ->
2005-07-11 01:07:59 -07:00
let row = Btype . row_repr row in
2000-09-06 03:21:07 -07:00
List . iter
( fun ( _ , f ) ->
match Btype . row_field_repr f with
Rpresent ( Some ty ) ->
2003-05-21 02:04:54 -07:00
compute_same ty
2001-03-02 16:14:35 -08:00
| Reither ( _ , tyl , _ , _ ) ->
2003-05-21 02:04:54 -07:00
List . iter compute_same tyl
2000-09-06 03:21:07 -07:00
| _ -> () )
2005-07-11 01:07:59 -07:00
row . row_fields ;
compute_same row . row_more
2002-04-18 00:27:47 -07:00
| Tpoly ( ty , _ ) ->
2003-05-21 02:04:54 -07:00
compute_same ty
2002-04-18 00:27:47 -07:00
| Tvar | Tnil | Tlink _ | Tunivar -> ()
2009-10-26 03:53:16 -07:00
| Tpackage ( _ , _ , tyl ) ->
List . iter ( compute_variance_rec true true true ) tyl
2000-09-06 03:21:07 -07:00
end
in
2003-05-21 02:04:54 -07:00
compute_variance_rec nega posi cntr ty ;
2000-09-06 03:21:07 -07:00
List . iter
2003-05-21 02:04:54 -07:00
( fun ( ty , covar , convar , ctvar ) ->
2000-09-06 03:21:07 -07:00
if TypeSet . mem ty ! pvisited then covar := true ;
2003-05-21 02:04:54 -07:00
if TypeSet . mem ty ! nvisited then convar := true ;
if TypeSet . mem ty ! cvisited then ctvar := true )
2000-09-06 03:21:07 -07:00
tvl
2004-12-09 04:40:53 -08:00
let make_variance ty = ( ty , ref false , ref false , ref false )
let whole_type decl =
match decl . type_kind with
2010-09-12 22:28:30 -07:00
| Type_generalized_variant tll ->
2004-12-09 04:40:53 -08:00
Btype . newgenty
2010-09-12 22:28:30 -07:00
( Ttuple ( List . map ( fun ( _ , tl , _ (* added by me *) ) -> Btype . newgenty ( Ttuple tl ) ) tll ) ) (* GAH: WHAT? *)
| Type_variant tll ->
Btype . newgenty
( Ttuple ( List . map ( fun ( _ , tl ) -> Btype . newgenty ( Ttuple tl ) ) tll ) ) (* GAH: WHAT? *)
2007-10-09 03:29:37 -07:00
| Type_record ( ftl , _ ) ->
2004-12-09 04:40:53 -08:00
Btype . newgenty
( Ttuple ( List . map ( fun ( _ , _ , ty ) -> ty ) ftl ) )
| Type_abstract ->
match decl . type_manifest with
Some ty -> ty
| _ -> Btype . newgenty ( Ttuple [] )
2005-08-13 13:59:37 -07:00
let compute_variance_decl env check decl ( required , loc ) =
2000-09-07 03:57:32 -07:00
if decl . type_kind = Type_abstract && decl . type_manifest = None then
2003-05-21 02:04:54 -07:00
List . map ( fun ( c , n ) -> if c | | n then ( c , n , n ) else ( true , true , true ) )
required
2000-09-07 03:57:32 -07:00
else
2004-12-09 04:40:53 -08:00
let params = List . map Btype . repr decl . type_params in
let tvl0 = List . map make_variance params in
2005-08-13 13:59:37 -07:00
let fvl = if check then Ctype . free_variables ( whole_type decl ) else [] in
2004-12-09 04:40:53 -08:00
let fvl = List . filter ( fun v -> not ( List . memq v params ) ) fvl in
let tvl1 = List . map make_variance fvl in
let tvl2 = List . map make_variance fvl in
let tvl = tvl0 @ tvl1 in
2010-09-18 21:55:40 -07:00
let is_gadt =
match decl . type_kind with
| Type_generalized_variant tll -> (* GAH: what in the blazes *)
let ret = ref false in
List . iter
( function
| ( _ , _ , Some _ ) ->
ret := true ;
| _ -> () )
tll ;
! ret
| _ -> false
in
if is_gadt then
List . map ( fun _ -> ( true , true , true ) ) params
else
begin begin match decl . type_kind with
2010-09-12 22:28:30 -07:00
| Type_abstract ->
2000-09-07 03:57:32 -07:00
begin match decl . type_manifest with
None -> assert false
2003-05-21 02:04:54 -07:00
| Some ty -> compute_variance env tvl true false false ty
2000-09-06 03:21:07 -07:00
end
2010-09-12 22:28:30 -07:00
| Type_variant tll -> (* GAH: what in the blazes *)
2000-09-06 03:21:07 -07:00
List . iter
2003-05-21 02:04:54 -07:00
( fun ( _ , tl ) ->
2010-09-12 22:28:30 -07:00
List . iter ( compute_variance env tvl true false false ) tl )
tll
| Type_generalized_variant tll -> (* GAH: what in the blazes *)
List . iter
( fun ( _ , tl , ret_type_opt ) ->
match ret_type_opt with
| None ->
List . iter ( compute_variance env tvl true false false ) tl
| Some ret_type ->
2010-09-18 21:55:40 -07:00
fatal_error " gadt not properly handled " )
tll ;
2007-10-09 03:29:37 -07:00
| Type_record ( ftl , _ ) ->
2000-09-06 03:21:07 -07:00
List . iter
2003-05-21 02:04:54 -07:00
( fun ( _ , mut , ty ) ->
2005-08-13 13:59:37 -07:00
let cn = ( mut = Mutable ) in
compute_variance env tvl true cn cn ty )
2000-09-06 03:21:07 -07:00
ftl
2003-07-02 02:14:35 -07:00
end ;
2009-05-20 04:52:42 -07:00
let required =
2005-08-15 17:48:56 -07:00
List . map ( fun ( c , n as r ) -> if c | | n then r else ( true , true ) )
required
2004-12-09 17:52:12 -08:00
in
2004-12-09 04:40:53 -08:00
List . iter2
( fun ( ty , co , cn , ct ) ( c , n ) ->
2009-05-20 04:52:42 -07:00
if ty . desc < > Tvar then begin
2004-12-09 04:40:53 -08:00
co := c ; cn := n ; ct := n ;
compute_variance env tvl2 c n n ty
end )
tvl0 required ;
2005-08-13 13:59:37 -07:00
List . iter2
( fun ( ty , c1 , n1 , t1 ) ( _ , c2 , n2 , t2 ) ->
2010-09-18 21:55:40 -07:00
if ! c1 && not ! c2 | | ! n1 && not ! n2
2005-08-13 13:59:37 -07:00
(* || !t1 && not !t2 && decl.type_kind = Type_abstract *)
then raise ( Error ( loc ,
if not ( ! c2 | | ! n2 ) then Unbound_type_var ( ty , decl )
else Bad_variance ( 0 , ( ! c1 , ! n1 ) , ( ! c2 , ! n2 ) ) ) ) )
tvl1 tvl2 ;
let pos = ref 0 in
2000-09-07 03:57:32 -07:00
List . map2
2003-05-21 02:04:54 -07:00
( fun ( _ , co , cn , ct ) ( c , n ) ->
2005-08-13 13:59:37 -07:00
incr pos ;
if ! co && not c | | ! cn && not n
then raise ( Error ( loc , Bad_variance ( ! pos , ( ! co , ! cn ) , ( c , n ) ) ) ) ;
2009-05-20 04:52:42 -07:00
if decl . type_private = Private then ( c , n , n ) else
2003-05-23 00:51:37 -07:00
let ct = if decl . type_kind = Type_abstract then ct else cn in
2003-05-21 02:04:54 -07:00
( ! co , ! cn , ! ct ) )
2004-12-09 04:40:53 -08:00
tvl0 required
2010-09-18 21:55:40 -07:00
end
2004-12-09 04:40:53 -08:00
let is_sharp id =
let s = Ident . name id in
String . length s > 0 && s . [ 0 ] = '#'
2000-09-06 03:21:07 -07:00
2000-09-07 03:57:32 -07:00
let rec compute_variance_fixpoint env decls required variances =
2000-09-06 03:21:07 -07:00
let new_decls =
List . map2
( fun ( id , decl ) variance -> id , { decl with type_variance = variance } )
decls variances
in
let new_env =
List . fold_right ( fun ( id , decl ) env -> Env . add_type id decl env )
new_decls env
in
let new_variances =
2004-12-09 04:40:53 -08:00
List . map2
2005-08-13 13:59:37 -07:00
( fun ( id , decl ) -> compute_variance_decl new_env false decl )
2000-09-07 03:57:32 -07:00
new_decls required
2000-09-06 03:21:07 -07:00
in
let new_variances =
2003-05-21 02:04:54 -07:00
List . map2
( List . map2 ( fun ( c1 , n1 , t1 ) ( c2 , n2 , t2 ) -> c1 | | c2 , n1 | | n2 , t1 | | t2 ) )
2000-09-06 03:21:07 -07:00
new_variances variances in
2005-08-13 13:59:37 -07:00
if new_variances < > variances then
2000-09-07 03:57:32 -07:00
compute_variance_fixpoint env decls required new_variances
2005-08-13 13:59:37 -07:00
else begin
List . iter2
( fun ( id , decl ) req -> if not ( is_sharp id ) then
ignore ( compute_variance_decl new_env true decl req ) )
new_decls required ;
2010-09-18 21:55:40 -07:00
2005-08-13 13:59:37 -07:00
new_decls , new_env
end
2000-09-06 03:21:07 -07:00
2004-12-09 04:40:53 -08:00
let init_variance ( id , decl ) =
List . map ( fun _ -> ( false , false , false ) ) decl . type_params
2000-09-06 03:21:07 -07:00
(* for typeclass.ml *)
2004-12-09 04:40:53 -08:00
let compute_variance_decls env cldecls =
let decls , required =
List . fold_right
( fun ( obj_id , obj_abbr , cl_abbr , clty , cltydef , required ) ( decls , req ) ->
( obj_id , obj_abbr ) :: decls , required :: req )
cldecls ( [] , [] )
2003-05-21 02:04:54 -07:00
in
2004-12-09 04:40:53 -08:00
let variances = List . map init_variance decls in
let ( decls , _ ) = compute_variance_fixpoint env decls required variances in
List . map2
( fun ( _ , decl ) ( _ , _ , cl_abbr , clty , cltydef , _ ) ->
let variance = List . map ( fun ( c , n , t ) -> ( c , n ) ) decl . type_variance in
( decl , { cl_abbr with type_variance = decl . type_variance } ,
{ clty with cty_variance = variance } ,
{ cltydef with clty_variance = variance } ) )
decls cldecls
2000-09-06 03:21:07 -07:00
2010-04-29 23:26:51 -07:00
(* Check multiple declarations of labels/constructors *)
2010-04-29 22:59:40 -07:00
let check_duplicates name_sdecl_list =
2010-04-29 23:26:51 -07:00
let labels = Hashtbl . create 7 and constrs = Hashtbl . create 7 in
2010-04-29 22:59:40 -07:00
List . iter
( fun ( name , sdecl ) -> match sdecl . ptype_kind with
Ptype_variant cl ->
List . iter
2010-09-12 22:28:30 -07:00
( fun ( cname , _ , _ , loc ) -> (* probably right *)
2010-04-29 22:59:40 -07:00
try
let name' = Hashtbl . find constrs cname in
2010-04-29 23:26:51 -07:00
Location . prerr_warning loc
( Warnings . Duplicate_definitions
( " constructor " , cname , name' , name ) )
2010-04-29 22:59:40 -07:00
with Not_found -> Hashtbl . add constrs cname name )
cl
| Ptype_record fl ->
List . iter
( fun ( cname , _ , _ , loc ) ->
try
2010-04-29 23:26:51 -07:00
let name' = Hashtbl . find labels cname in
Location . prerr_warning loc
( Warnings . Duplicate_definitions ( " label " , cname , name' , name ) )
with Not_found -> Hashtbl . add labels cname name )
2010-04-29 22:59:40 -07:00
fl
| Ptype_abstract -> () )
name_sdecl_list
2006-11-01 17:10:04 -08:00
(* Force recursion to go through id for private types *)
let name_recursion sdecl id decl =
match decl with
2007-10-09 03:29:37 -07:00
| { type_kind = Type_abstract ;
type_manifest = Some ty ;
type_private = Private ; } when is_fixed_type sdecl ->
let ty = Ctype . repr ty in
let ty' = Btype . newty2 ty . level ty . desc in
if Ctype . deep_occur ty ty' then
let td = Tconstr ( Path . Pident id , decl . type_params , ref Mnil ) in
Btype . link_type ty ( Btype . newty2 ty . level td ) ;
{ decl with type_manifest = Some ty' }
else decl
2006-11-01 17:10:04 -08:00
| _ -> decl
2010-09-18 21:55:40 -07:00
1995-05-04 03:15:53 -07:00
(* Translate a set of mutually recursive type declarations *)
let transl_type_decl env name_sdecl_list =
2005-03-22 19:08:37 -08:00
(* Add dummy types for fixed rows *)
let fixed_types =
2007-10-09 03:29:37 -07:00
List . filter ( fun ( _ , sd ) -> is_fixed_type sd ) name_sdecl_list
2005-03-22 19:08:37 -08:00
in
let name_sdecl_list =
List . map
( fun ( name , sdecl ) ->
name ^ " #row " ,
{ sdecl with ptype_kind = Ptype_abstract ; ptype_manifest = None } )
fixed_types
@ name_sdecl_list
in
1997-02-20 12:39:02 -08:00
(* Create identifiers. *)
let id_list =
List . map ( fun ( name , _ ) -> Ident . create name ) name_sdecl_list
in
(*
Since we've introduced fresh idents , make sure the definition
level is at least the binding time of these events . Otherwise ,
passing one of the recursively - defined type constrs as argument
to an abbreviation may fail .
* )
1996-09-24 08:45:58 -07:00
Ctype . init_def ( Ident . current_time () ) ;
1997-02-20 12:39:02 -08:00
Ctype . begin_def () ;
(* Enter types. *)
2000-05-23 23:19:39 -07:00
let temp_env = List . fold_left2 enter_type env name_sdecl_list id_list in
1997-02-20 12:39:02 -08:00
(* Translate each declaration. *)
1995-08-28 04:23:33 -07:00
let decls =
2000-05-23 23:19:39 -07:00
List . map2 ( transl_declaration temp_env ) name_sdecl_list id_list in
2010-04-29 22:59:40 -07:00
(* Check for duplicates *)
check_duplicates name_sdecl_list ;
1997-02-20 12:39:02 -08:00
(* Build the final env. *)
1995-05-04 03:15:53 -07:00
let newenv =
1995-08-28 04:23:33 -07:00
List . fold_right
( fun ( id , decl ) env -> Env . add_type id decl env )
1997-02-20 12:39:02 -08:00
decls env
in
2000-08-03 20:29:42 -07:00
(* Update stubs *)
List . iter2
( fun id ( _ , sdecl ) -> update_type temp_env newenv id sdecl . ptype_loc )
id_list name_sdecl_list ;
(* Generalize type declarations. *)
Ctype . end_def () ;
List . iter ( fun ( _ , decl ) -> generalize_decl decl ) decls ;
2003-07-03 03:00:53 -07:00
(* Check for ill-formed abbrevs *)
let id_loc_list =
List . map2 ( fun id ( _ , sdecl ) -> ( id , sdecl . ptype_loc ) )
id_list name_sdecl_list
in
List . iter ( check_abbrev_recursion newenv id_loc_list ) decls ;
1998-06-24 12:22:26 -07:00
(* Check that all type variable are closed *)
List . iter2
( fun ( _ , sdecl ) ( id , decl ) ->
match Ctype . closed_type_decl decl with
2005-08-13 13:59:37 -07:00
Some ty -> raise ( Error ( sdecl . ptype_loc , Unbound_type_var ( ty , decl ) ) )
1998-06-24 12:22:26 -07:00
| None -> () )
name_sdecl_list decls ;
1997-02-20 12:39:02 -08:00
(* Check re-exportation *)
List . iter2 ( check_abbrev newenv ) name_sdecl_list decls ;
2000-05-23 23:19:39 -07:00
(* Check that constraints are enforced *)
2003-06-28 03:46:32 -07:00
List . iter2 ( check_constraints newenv ) name_sdecl_list decls ;
2006-11-01 17:10:04 -08:00
(* Name recursion *)
let decls =
List . map2 ( fun ( _ , sdecl ) ( id , decl ) -> id , name_recursion sdecl id decl )
name_sdecl_list decls
in
2000-09-06 03:21:07 -07:00
(* Add variances to the environment *)
2000-09-07 03:57:32 -07:00
let required =
List . map ( fun ( _ , sdecl ) -> sdecl . ptype_variance , sdecl . ptype_loc )
name_sdecl_list
in
2010-09-18 21:55:40 -07:00
2000-09-06 03:21:07 -07:00
let final_decls , final_env =
2004-12-09 04:40:53 -08:00
compute_variance_fixpoint env decls required ( List . map init_variance decls )
in
1995-05-04 03:15:53 -07:00
(* Done *)
2000-09-06 03:21:07 -07:00
( final_decls , final_env )
1995-05-04 03:15:53 -07:00
(* Translate an exception declaration *)
2009-07-20 04:51:50 -07:00
let transl_closed_type env sty =
let ty = transl_simple_type env true sty in
match Ctype . free_variables ty with
| [] -> ty
| tv :: _ -> raise ( Error ( sty . ptyp_loc , Unbound_type_var_exc ( tv , ty ) ) )
1995-05-04 03:15:53 -07:00
let transl_exception env excdecl =
reset_type_variables () ;
1997-02-20 12:39:02 -08:00
Ctype . begin_def () ;
2009-07-20 04:51:50 -07:00
let types = List . map ( transl_closed_type env ) excdecl in
1997-02-20 12:39:02 -08:00
Ctype . end_def () ;
List . iter Ctype . generalize types ;
types
1995-05-04 03:15:53 -07:00
2000-03-12 05:10:29 -08:00
(* Translate an exception rebinding *)
let transl_exn_rebind env loc lid =
let cdescr =
try
Env . lookup_constructor lid env
with Not_found ->
raise ( Error ( loc , Unbound_exception lid ) ) in
match cdescr . cstr_tag with
Cstr_exception path -> ( path , cdescr . cstr_args )
| _ -> raise ( Error ( loc , Not_an_exception lid ) )
1995-07-25 04:40:07 -07:00
(* Translate a value declaration *)
let transl_value_decl env valdecl =
let ty = Typetexp . transl_type_scheme env valdecl . pval_type in
1997-05-13 07:07:00 -07:00
match valdecl . pval_prim with
[] ->
{ val_type = ty ; val_kind = Val_reg }
| decl ->
let arity = Ctype . arity ty in
if arity = 0 then
raise ( Error ( valdecl . pval_type . ptyp_loc , Null_arity_external ) ) ;
let prim = Primitive . parse_declaration arity decl in
2000-06-05 05:18:30 -07:00
if ! Clflags . native_code
&& prim . prim_arity > 5
&& prim . prim_native_name = " "
then raise ( Error ( valdecl . pval_type . ptyp_loc , Missing_native_external ) ) ;
1997-05-13 07:07:00 -07:00
{ val_type = ty ; val_kind = Val_prim prim }
1995-07-25 04:40:07 -07:00
1995-09-28 03:42:38 -07:00
(* Translate a "with" constraint -- much simplified version of
transl_type_decl . * )
2006-11-01 17:10:04 -08:00
let transl_with_constraint env id row_path sdecl =
1995-09-28 03:42:38 -07:00
reset_type_variables () ;
1996-04-22 04:15:41 -07:00
Ctype . begin_def () ;
1995-09-28 03:42:38 -07:00
let params =
try
2003-03-07 00:59:15 -08:00
List . map ( enter_type_variable true sdecl . ptype_loc ) sdecl . ptype_params
1995-09-28 03:42:38 -07:00
with Already_bound ->
raise ( Error ( sdecl . ptype_loc , Repeated_parameter ) ) in
1997-02-20 12:39:02 -08:00
List . iter
1998-06-24 12:22:26 -07:00
( function ( ty , ty' , loc ) ->
1997-02-20 12:39:02 -08:00
try
1998-06-24 12:22:26 -07:00
Ctype . unify env ( transl_simple_type env false ty )
( transl_simple_type env false ty' )
2001-12-25 19:43:41 -08:00
with Ctype . Unify tr ->
2010-09-18 21:55:40 -07:00
raise ( Error ( loc , Unconsistent_constraint tr ) ) ) (* GAH : Unconsistent is not a word *)
1997-02-20 12:39:02 -08:00
sdecl . ptype_cstrs ;
2007-10-09 03:29:37 -07:00
let no_row = not ( is_fixed_type sdecl ) in
1997-02-20 12:39:02 -08:00
let decl =
{ type_params = params ;
type_arity = List . length params ;
type_kind = Type_abstract ;
2007-10-09 03:29:37 -07:00
type_private = sdecl . ptype_private ;
1997-02-20 12:39:02 -08:00
type_manifest =
1995-09-28 03:42:38 -07:00
begin match sdecl . ptype_manifest with
None -> None
2005-03-22 19:08:37 -08:00
| Some sty ->
Some ( transl_simple_type env no_row sty )
2000-09-06 03:21:07 -07:00
end ;
type_variance = [] ;
}
1997-02-20 12:39:02 -08:00
in
2005-03-22 19:08:37 -08:00
begin match row_path with None -> ()
| Some p -> set_fixed_row env sdecl . ptype_loc p decl
end ;
2005-08-13 13:59:37 -07:00
begin match Ctype . closed_type_decl decl with None -> ()
| Some ty -> raise ( Error ( sdecl . ptype_loc , Unbound_type_var ( ty , decl ) ) )
end ;
2006-11-01 17:10:04 -08:00
let decl = name_recursion sdecl id decl in
2000-09-06 03:21:07 -07:00
let decl =
2000-09-07 03:57:32 -07:00
{ decl with type_variance =
2004-12-09 04:40:53 -08:00
compute_variance_decl env false decl
( sdecl . ptype_variance , sdecl . ptype_loc ) } in
1997-02-20 12:39:02 -08:00
Ctype . end_def () ;
generalize_decl decl ;
decl
1995-09-28 03:42:38 -07:00
2003-06-19 08:53:53 -07:00
(* Approximate a type declaration: just make all types abstract *)
let abstract_type_decl arity =
let rec make_params n =
if n < = 0 then [] else Ctype . newvar () :: make_params ( n - 1 ) in
Ctype . begin_def () ;
let decl =
{ type_params = make_params arity ;
type_arity = arity ;
type_kind = Type_abstract ;
2007-10-09 03:29:37 -07:00
type_private = Public ;
2003-06-19 08:53:53 -07:00
type_manifest = None ;
type_variance = replicate_list ( true , true , true ) arity } in
Ctype . end_def () ;
generalize_decl decl ;
decl
let approx_type_decl env name_sdecl_list =
List . map
2005-08-13 13:59:37 -07:00
( fun ( name , sdecl ) ->
2003-06-19 08:53:53 -07:00
( Ident . create name ,
abstract_type_decl ( List . length sdecl . ptype_params ) ) )
name_sdecl_list
2003-07-03 03:00:53 -07:00
(* Variant of check_abbrev_recursion to check the well-formedness
conditions on type abbreviations defined within recursive modules . * )
2003-07-01 06:05:43 -07:00
let check_recmod_typedecl env loc recmod_ids path decl =
(* recmod_ids is the list of recursively-defined module idents.
( path , decl ) is the type declaration to be checked . * )
2003-07-03 03:00:53 -07:00
check_recursion env loc path decl
2008-08-07 02:29:22 -07:00
( fun path -> List . exists ( fun id -> Path . isfree id path ) recmod_ids )
2003-07-01 06:05:43 -07:00
1997-02-20 12:39:02 -08:00
(* * * * Error report * * * *)
1995-05-04 03:15:53 -07:00
2000-03-06 14:12:09 -08:00
open Format
1995-05-04 03:15:53 -07:00
2009-07-20 04:51:50 -07:00
let explain_unbound ppf tv tl typ kwd lab =
try
let ti = List . find ( fun ti -> Ctype . deep_occur tv ( typ ti ) ) tl in
let ty0 = (* Hack to force aliasing when needed *)
Btype . newgenty ( Tobject ( tv , ref None ) ) in
Printtyp . reset_and_mark_loops_list [ typ ti ; ty0 ] ;
fprintf ppf
" .@.@[<hov2>In %s@ %s%a@;<1 -2>the variable %a is unbound@] "
kwd ( lab ti ) Printtyp . type_expr ( typ ti ) Printtyp . type_expr tv
with Not_found -> ()
let explain_unbound_single ppf tv ty =
let trivial ty =
explain_unbound ppf tv [ ty ] ( fun t -> t ) " type " ( fun _ -> " " ) in
match ( Ctype . repr ty ) . desc with
Tobject ( fi , _ ) ->
let ( tl , rv ) = Ctype . flatten_fields fi in
if rv = = tv then trivial ty else
explain_unbound ppf tv tl ( fun ( _ , _ , t ) -> t )
" method " ( fun ( lab , _ , _ ) -> lab ^ " : " )
| Tvariant row ->
let row = Btype . row_repr row in
if row . row_more = = tv then trivial ty else
explain_unbound ppf tv row . row_fields
( fun ( l , f ) -> match Btype . row_field_repr f with
Rpresent ( Some t ) -> t
| Reither ( _ , [ t ] , _ , _ ) -> t
| Reither ( _ , tl , _ , _ ) -> Btype . newgenty ( Ttuple tl )
| _ -> Btype . newgenty ( Ttuple [] ) )
" case " ( fun ( lab , _ ) -> " ` " ^ lab ^ " of " )
| _ -> trivial ty
2000-03-06 14:12:09 -08:00
let report_error ppf = function
| Repeated_parameter ->
fprintf ppf " A type parameter occurs several times "
1995-05-04 03:15:53 -07:00
| Duplicate_constructor s ->
2000-03-06 14:12:09 -08:00
fprintf ppf " Two constructors are named %s " s
1995-05-22 08:43:44 -07:00
| Too_many_constructors ->
2010-05-21 08:13:47 -07:00
fprintf ppf
" @[Too many non-constant constructors@ -- maximum is %i %s@] "
( Config . max_tag + 1 ) " non-constant constructors "
1995-05-04 03:15:53 -07:00
| Duplicate_label s ->
2000-03-06 14:12:09 -08:00
fprintf ppf " Two labels are named %s " s
1995-05-04 03:15:53 -07:00
| Recursive_abbrev s ->
2000-03-06 14:12:09 -08:00
fprintf ppf " The type abbreviation %s is cyclic " s
2010-05-20 20:36:52 -07:00
| Definition_mismatch ( ty , errs ) ->
2000-03-06 14:12:09 -08:00
Printtyp . reset_and_mark_loops ty ;
2010-05-23 23:52:16 -07:00
fprintf ppf " @[<v>@[<hov>%s@ %s@;<1 2>%a@]%a@] "
2010-05-21 08:13:47 -07:00
" This variant or record definition " " does not match that of type "
Printtyp . type_expr ty
( Includecore . report_type_mismatch " the original " " this " " definition " )
2010-05-20 20:36:52 -07:00
errs
2000-05-24 01:06:33 -07:00
| Constraint_failed ( ty , ty' ) ->
fprintf ppf " Constraints are not satisfied in this type.@. " ;
2000-05-23 23:19:39 -07:00
Printtyp . reset_and_mark_loops ty ;
Printtyp . mark_loops ty' ;
2000-05-24 01:06:33 -07:00
fprintf ppf " @[<hv>Type@ %a@ should be an instance of@ %a@] "
2000-05-23 23:19:39 -07:00
Printtyp . type_expr ty Printtyp . type_expr ty'
2003-07-01 06:05:43 -07:00
| Parameters_differ ( path , ty , ty' ) ->
2000-05-24 19:09:13 -07:00
Printtyp . reset_and_mark_loops ty ;
Printtyp . mark_loops ty' ;
fprintf ppf
2003-07-01 06:05:43 -07:00
" @[<hv>In the definition of %s, type@ %a@ should be@ %a@] "
( Path . name path ) Printtyp . type_expr ty Printtyp . type_expr ty'
2001-12-25 19:43:41 -08:00
| Unconsistent_constraint trace ->
fprintf ppf " The type constraints are not consistent.@. " ;
Printtyp . report_unification_error ppf trace
( fun ppf -> fprintf ppf " Type " )
( fun ppf -> fprintf ppf " is not compatible with type " )
1997-02-20 12:39:02 -08:00
| Type_clash trace ->
2000-03-06 14:12:09 -08:00
Printtyp . report_unification_error ppf trace
( function ppf ->
fprintf ppf " This type constructor expands to type " )
( function ppf ->
2009-05-20 04:52:42 -07:00
fprintf ppf " but is used here with type " )
1997-05-13 07:07:00 -07:00
| Null_arity_external ->
2000-03-06 14:12:09 -08:00
fprintf ppf " External identifiers must be functions "
2000-06-05 05:18:30 -07:00
| Missing_native_external ->
fprintf ppf " @[<hv>An external function with more than 5 arguments \
2009-05-20 04:52:42 -07:00
requires a second stub function @ \
2000-06-05 05:18:30 -07:00
for native - code compilation @ ] "
2005-08-13 13:59:37 -07:00
| Unbound_type_var ( ty , decl ) ->
fprintf ppf " A type variable is unbound in this type declaration " ;
let ty = Ctype . repr ty in
2009-07-20 04:51:50 -07:00
begin match decl . type_kind , decl . type_manifest with
2010-09-12 22:28:30 -07:00
| Type_generalized_variant tl , _ ->
explain_unbound ppf ty tl ( fun ( _ , tl , _ ) ->
Btype . newgenty ( Ttuple tl ) )
" case " ( fun ( lab , _ , _ ) -> lab ^ " of " )
| Type_variant tl , _ ->
explain_unbound ppf ty tl ( fun ( _ , tl ) ->
Btype . newgenty ( Ttuple tl ) )
" case " ( fun ( lab , _ ) -> lab ^ " of " )
2007-10-09 03:29:37 -07:00
| Type_record ( tl , _ ) , _ ->
2009-07-20 04:51:50 -07:00
explain_unbound ppf ty tl ( fun ( _ , _ , t ) -> t )
2005-08-13 13:59:37 -07:00
" field " ( fun ( lab , _ , _ ) -> lab ^ " : " )
| Type_abstract , Some ty' ->
2009-07-20 04:51:50 -07:00
explain_unbound_single ppf ty ty'
2005-08-13 13:59:37 -07:00
| _ -> ()
end
2009-07-20 04:51:50 -07:00
| Unbound_type_var_exc ( tv , ty ) ->
fprintf ppf " A type variable is unbound in this exception declaration " ;
explain_unbound_single ppf ( Ctype . repr tv ) ty
2000-03-12 05:10:29 -08:00
| Unbound_exception lid ->
fprintf ppf " Unbound exception constructor@ %a " Printtyp . longident lid
| Not_an_exception lid ->
fprintf ppf " The constructor@ %a@ is not an exception "
Printtyp . longident lid
2005-08-13 13:59:37 -07:00
| Bad_variance ( n , v1 , v2 ) ->
let variance = function
( true , true ) -> " invariant "
| ( true , false ) -> " covariant "
| ( false , true ) -> " contravariant "
| ( false , false ) -> " unrestricted "
in
2009-05-20 04:52:42 -07:00
let suffix n =
let teen = ( n mod 100 ) / 10 = 1 in
match n mod 10 with
| 1 when not teen -> " st "
| 2 when not teen -> " nd "
| 3 when not teen -> " rd "
| _ -> " th "
in
2005-08-13 13:59:37 -07:00
if n < 1 then
fprintf ppf " %s@ %s@ %s "
" In this definition, a type variable "
" has a variance that is not reflected "
2009-05-20 04:52:42 -07:00
" by its occurrence in type parameters. "
2005-08-13 13:59:37 -07:00
else
fprintf ppf " %s@ %s@ %s %d%s %s %s,@ %s %s "
" In this definition, expected parameter "
" variances are not satisfied. "
2009-05-20 04:52:42 -07:00
" The " n ( suffix n )
2005-08-13 13:59:37 -07:00
" type parameter was expected to be " ( variance v2 )
" but it is " ( variance v1 )
2001-09-28 15:55:27 -07:00
| Unavailable_type_constructor p ->
fprintf ppf " The definition of type %a@ is unavailable " Printtyp . path p
2005-03-22 19:08:37 -08:00
| Bad_fixed_type r ->
fprintf ppf " This fixed type %s " r