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
|
|
|
(* *)
|
|
|
|
(* 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
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Operations on module types *)
|
|
|
|
|
2007-10-19 06:25:21 -07:00
|
|
|
open Asttypes
|
1995-05-04 03:15:53 -07:00
|
|
|
open Path
|
1996-09-23 04:33:27 -07:00
|
|
|
open Types
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
|
|
|
|
let rec scrape env mty =
|
|
|
|
match mty with
|
|
|
|
Tmty_ident p ->
|
1995-11-03 05:23:03 -08:00
|
|
|
begin try
|
1999-11-25 08:47:47 -08:00
|
|
|
scrape env (Env.find_modtype_expansion p env)
|
1995-11-03 05:23:03 -08:00
|
|
|
with Not_found ->
|
|
|
|
mty
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
| _ -> mty
|
|
|
|
|
2004-02-14 09:38:02 -08:00
|
|
|
let freshen mty =
|
|
|
|
Subst.modtype Subst.identity mty
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let rec strengthen env mty p =
|
|
|
|
match scrape env mty with
|
|
|
|
Tmty_signature sg ->
|
|
|
|
Tmty_signature(strengthen_sig env sg p)
|
2009-07-15 07:06:37 -07:00
|
|
|
| Tmty_functor(param, arg, res) when !Clflags.applicative_functors ->
|
1995-08-23 04:55:54 -07:00
|
|
|
Tmty_functor(param, arg, strengthen env res (Papply(p, Pident param)))
|
1995-05-04 03:15:53 -07:00
|
|
|
| mty ->
|
|
|
|
mty
|
|
|
|
|
|
|
|
and strengthen_sig env sg p =
|
|
|
|
match sg with
|
|
|
|
[] -> []
|
|
|
|
| (Tsig_value(id, desc) as sigelt) :: rem ->
|
|
|
|
sigelt :: strengthen_sig env rem p
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_type(id, decl, rs) :: rem ->
|
1995-05-04 03:15:53 -07:00
|
|
|
let newdecl =
|
1995-09-26 13:23:29 -07:00
|
|
|
match decl.type_manifest with
|
2007-10-19 06:25:21 -07:00
|
|
|
Some ty when decl.type_private = Public -> decl
|
2005-09-28 00:18:30 -07:00
|
|
|
| _ ->
|
2009-07-20 04:51:50 -07:00
|
|
|
let manif =
|
|
|
|
Some(Btype.newgenty(Tconstr(Pdot(p, Ident.name id, nopos),
|
|
|
|
decl.type_params, ref Mnil))) in
|
|
|
|
if decl.type_kind = Type_abstract then
|
|
|
|
{ decl with type_private = Public; type_manifest = manif }
|
|
|
|
else
|
|
|
|
{ decl with type_manifest = manif }
|
2005-09-28 00:18:30 -07:00
|
|
|
in
|
2004-06-12 01:55:49 -07:00
|
|
|
Tsig_type(id, newdecl, rs) :: strengthen_sig env rem p
|
1995-05-04 03:15:53 -07:00
|
|
|
| (Tsig_exception(id, d) as sigelt) :: rem ->
|
|
|
|
sigelt :: strengthen_sig env rem p
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_module(id, mty, rs) :: rem ->
|
|
|
|
Tsig_module(id, strengthen env mty (Pdot(p, Ident.name id, nopos)), rs)
|
|
|
|
:: strengthen_sig (Env.add_module id mty env) rem p
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Need to add the module in case it defines manifest module types *)
|
|
|
|
| Tsig_modtype(id, decl) :: rem ->
|
|
|
|
let newdecl =
|
|
|
|
match decl with
|
|
|
|
Tmodtype_abstract ->
|
|
|
|
Tmodtype_manifest(Tmty_ident(Pdot(p, Ident.name id, nopos)))
|
|
|
|
| Tmodtype_manifest _ ->
|
|
|
|
decl in
|
|
|
|
Tsig_modtype(id, newdecl) ::
|
|
|
|
strengthen_sig (Env.add_modtype id decl env) rem p
|
|
|
|
(* Need to add the module type in case it is manifest *)
|
2004-06-12 01:55:49 -07:00
|
|
|
| (Tsig_class(id, decl, rs) as sigelt) :: rem ->
|
1996-04-22 04:15:41 -07:00
|
|
|
sigelt :: strengthen_sig env rem p
|
2004-06-12 01:55:49 -07:00
|
|
|
| (Tsig_cltype(id, decl, rs) as sigelt) :: rem ->
|
1998-06-24 12:22:26 -07:00
|
|
|
sigelt :: strengthen_sig env rem p
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* In nondep_supertype, env is only used for the type it assigns to id.
|
|
|
|
Hence there is no need to keep env up-to-date by adding the bindings
|
|
|
|
traversed. *)
|
|
|
|
|
|
|
|
type variance = Co | Contra | Strict
|
|
|
|
|
1995-05-22 04:58:12 -07:00
|
|
|
let nondep_supertype env mid mty =
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2009-05-19 01:17:02 -07:00
|
|
|
let rec nondep_mty env va mty =
|
1995-05-04 03:15:53 -07:00
|
|
|
match mty with
|
|
|
|
Tmty_ident p ->
|
1997-04-01 12:53:02 -08:00
|
|
|
if Path.isfree mid p then
|
2009-05-19 01:17:02 -07:00
|
|
|
nondep_mty env va (Env.find_modtype_expansion p env)
|
1997-04-01 12:53:02 -08:00
|
|
|
else mty
|
1995-05-04 03:15:53 -07:00
|
|
|
| Tmty_signature sg ->
|
2009-05-19 01:17:02 -07:00
|
|
|
Tmty_signature(nondep_sig env va sg)
|
1995-05-04 03:15:53 -07:00
|
|
|
| Tmty_functor(param, arg, res) ->
|
|
|
|
let var_inv =
|
1996-04-22 04:15:41 -07:00
|
|
|
match va with Co -> Contra | Contra -> Co | Strict -> Strict in
|
2009-05-19 01:17:02 -07:00
|
|
|
Tmty_functor(param, nondep_mty env var_inv arg,
|
|
|
|
nondep_mty (Env.add_module param arg env) va res)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2009-05-19 01:17:02 -07:00
|
|
|
and nondep_sig env va = function
|
1995-05-04 03:15:53 -07:00
|
|
|
[] -> []
|
|
|
|
| item :: rem ->
|
2009-05-19 01:17:02 -07:00
|
|
|
let rem' = nondep_sig env va rem in
|
1995-05-04 03:15:53 -07:00
|
|
|
match item with
|
|
|
|
Tsig_value(id, d) ->
|
1995-10-17 03:02:47 -07:00
|
|
|
Tsig_value(id, {val_type = Ctype.nondep_type env mid d.val_type;
|
1996-04-22 04:15:41 -07:00
|
|
|
val_kind = d.val_kind}) :: rem'
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_type(id, d, rs) ->
|
|
|
|
Tsig_type(id, Ctype.nondep_type_decl env mid id (va = Co) d, rs)
|
|
|
|
:: rem'
|
1995-05-04 03:15:53 -07:00
|
|
|
| Tsig_exception(id, d) ->
|
1995-10-17 03:02:47 -07:00
|
|
|
Tsig_exception(id, List.map (Ctype.nondep_type env mid) d) :: rem'
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_module(id, mty, rs) ->
|
2009-05-19 01:17:02 -07:00
|
|
|
Tsig_module(id, nondep_mty env va mty, rs) :: rem'
|
1995-05-04 03:15:53 -07:00
|
|
|
| Tsig_modtype(id, d) ->
|
|
|
|
begin try
|
2009-05-19 01:17:02 -07:00
|
|
|
Tsig_modtype(id, nondep_modtype_decl env d) :: rem'
|
1995-05-04 03:15:53 -07:00
|
|
|
with Not_found ->
|
1996-04-22 04:15:41 -07:00
|
|
|
match va with
|
1995-05-04 03:15:53 -07:00
|
|
|
Co -> Tsig_modtype(id, Tmodtype_abstract) :: rem'
|
|
|
|
| _ -> raise Not_found
|
|
|
|
end
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_class(id, d, rs) ->
|
|
|
|
Tsig_class(id, Ctype.nondep_class_declaration env mid d, rs)
|
|
|
|
:: rem'
|
|
|
|
| Tsig_cltype(id, d, rs) ->
|
|
|
|
Tsig_cltype(id, Ctype.nondep_cltype_declaration env mid d, rs)
|
|
|
|
:: rem'
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2009-05-19 01:17:02 -07:00
|
|
|
and nondep_modtype_decl env = function
|
1995-05-04 03:15:53 -07:00
|
|
|
Tmodtype_abstract -> Tmodtype_abstract
|
2009-05-19 01:17:02 -07:00
|
|
|
| Tmodtype_manifest mty -> Tmodtype_manifest(nondep_mty env Strict mty)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
in
|
2009-05-19 01:17:02 -07:00
|
|
|
nondep_mty env Co mty
|
2003-06-19 08:53:53 -07:00
|
|
|
|
|
|
|
let enrich_typedecl env p decl =
|
|
|
|
match decl.type_manifest with
|
|
|
|
Some ty -> decl
|
|
|
|
| None ->
|
|
|
|
try
|
|
|
|
let orig_decl = Env.find_type p env in
|
|
|
|
if orig_decl.type_arity <> decl.type_arity
|
|
|
|
then decl
|
|
|
|
else {decl with type_manifest =
|
|
|
|
Some(Btype.newgenty(Tconstr(p, decl.type_params, ref Mnil)))}
|
|
|
|
with Not_found ->
|
|
|
|
decl
|
|
|
|
|
|
|
|
let rec enrich_modtype env p mty =
|
|
|
|
match mty with
|
|
|
|
Tmty_signature sg ->
|
|
|
|
Tmty_signature(List.map (enrich_item env p) sg)
|
|
|
|
| _ ->
|
|
|
|
mty
|
|
|
|
|
|
|
|
and enrich_item env p = function
|
2004-06-12 01:55:49 -07:00
|
|
|
Tsig_type(id, decl, rs) ->
|
|
|
|
Tsig_type(id,
|
|
|
|
enrich_typedecl env (Pdot(p, Ident.name id, nopos)) decl, rs)
|
|
|
|
| Tsig_module(id, mty, rs) ->
|
|
|
|
Tsig_module(id,
|
|
|
|
enrich_modtype env (Pdot(p, Ident.name id, nopos)) mty, rs)
|
2003-06-19 08:53:53 -07:00
|
|
|
| item -> item
|
2003-07-01 06:05:43 -07:00
|
|
|
|
|
|
|
let rec type_paths env p mty =
|
|
|
|
match scrape env mty with
|
|
|
|
Tmty_ident p -> []
|
|
|
|
| Tmty_signature sg -> type_paths_sig env p 0 sg
|
|
|
|
| Tmty_functor(param, arg, res) -> []
|
|
|
|
|
|
|
|
and type_paths_sig env p pos sg =
|
|
|
|
match sg with
|
|
|
|
[] -> []
|
|
|
|
| Tsig_value(id, decl) :: rem ->
|
|
|
|
let pos' = match decl.val_kind with Val_prim _ -> pos | _ -> pos + 1 in
|
|
|
|
type_paths_sig env p pos' rem
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_type(id, decl, _) :: rem ->
|
2003-07-01 06:05:43 -07:00
|
|
|
Pdot(p, Ident.name id, nopos) :: type_paths_sig env p pos rem
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_module(id, mty, _) :: rem ->
|
2003-07-01 06:05:43 -07:00
|
|
|
type_paths env (Pdot(p, Ident.name id, pos)) mty @
|
|
|
|
type_paths_sig (Env.add_module id mty env) p (pos+1) rem
|
|
|
|
| Tsig_modtype(id, decl) :: rem ->
|
|
|
|
type_paths_sig (Env.add_modtype id decl env) p pos rem
|
|
|
|
| (Tsig_exception _ | Tsig_class _) :: rem ->
|
|
|
|
type_paths_sig env p (pos+1) rem
|
|
|
|
| (Tsig_cltype _) :: rem ->
|
|
|
|
type_paths_sig env p pos rem
|
2004-04-09 06:32:28 -07:00
|
|
|
|
|
|
|
let rec no_code_needed env mty =
|
|
|
|
match scrape env mty with
|
|
|
|
Tmty_ident p -> false
|
|
|
|
| Tmty_signature sg -> no_code_needed_sig env sg
|
|
|
|
| Tmty_functor(_, _, _) -> false
|
|
|
|
|
|
|
|
and no_code_needed_sig env sg =
|
|
|
|
match sg with
|
|
|
|
[] -> true
|
|
|
|
| Tsig_value(id, decl) :: rem ->
|
|
|
|
begin match decl.val_kind with
|
|
|
|
| Val_prim _ -> no_code_needed_sig env rem
|
|
|
|
| _ -> false
|
|
|
|
end
|
2004-06-12 01:55:49 -07:00
|
|
|
| Tsig_module(id, mty, _) :: rem ->
|
2004-04-09 06:32:28 -07:00
|
|
|
no_code_needed env mty &&
|
|
|
|
no_code_needed_sig (Env.add_module id mty env) rem
|
|
|
|
| (Tsig_type _ | Tsig_modtype _ | Tsig_cltype _) :: rem ->
|
|
|
|
no_code_needed_sig env rem
|
|
|
|
| (Tsig_exception _ | Tsig_class _) :: rem ->
|
|
|
|
false
|