[commit: ghc] master: Fix #9097. (051d694)
git at git.haskell.org
git at git.haskell.org
Wed Jun 11 13:32:20 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/051d694fc978ad28ac3043d296cafddd3c2a7050/ghc
>---------------------------------------------------------------
commit 051d694fc978ad28ac3043d296cafddd3c2a7050
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Tue Jun 10 15:21:47 2014 -0400
Fix #9097.
`Any` is now an abstract (that is, no equations) closed type family.
>---------------------------------------------------------------
051d694fc978ad28ac3043d296cafddd3c2a7050
compiler/prelude/TysPrim.lhs | 16 ++++------------
compiler/prelude/primops.txt.pp | 9 ++++++---
2 files changed, 10 insertions(+), 15 deletions(-)
diff --git a/compiler/prelude/TysPrim.lhs b/compiler/prelude/TysPrim.lhs
index ae9a11e..0547c91 100644
--- a/compiler/prelude/TysPrim.lhs
+++ b/compiler/prelude/TysPrim.lhs
@@ -701,7 +701,7 @@ threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName PtrRep
Note [Any types]
~~~~~~~~~~~~~~~~
-The type constructor Any of kind forall k. k -> k has these properties:
+The type constructor Any of kind forall k. k has these properties:
* It is defined in module GHC.Prim, and exported so that it is
available to users. For this reason it's treated like any other
@@ -714,7 +714,7 @@ The type constructor Any of kind forall k. k -> k has these properties:
g :: ty ~ (Fst ty, Snd ty)
If Any was a *data* type, then we'd get inconsistency because 'ty'
could be (Any '(k1,k2)) and then we'd have an equality with Any on
- one side and '(,) on the other
+ one side and '(,) on the other. See also #9097.
* It is lifted, and hence represented by a pointer
@@ -771,20 +771,12 @@ anyTy :: Type
anyTy = mkTyConTy anyTyCon
anyTyCon :: TyCon
-anyTyCon = mkLiftedPrimTyCon anyTyConName kind [Nominal] PtrRep
- where kind = ForAllTy kKiVar (mkTyVarTy kKiVar)
-
-{- Can't do this yet without messing up kind proxies
--- RAE: I think you can now.
-anyTyCon :: TyCon
-anyTyCon = mkSynTyCon anyTyConName kind [kKiVar]
+anyTyCon = mkSynTyCon anyTyConName kind [kKiVar] [Nominal]
syn_rhs
NoParentTyCon
where
kind = ForAllTy kKiVar (mkTyVarTy kKiVar)
- syn_rhs = SynFamilyTyCon { synf_open = False, synf_injective = True }
- -- NB Closed, injective
--}
+ syn_rhs = AbstractClosedSynFamilyTyCon
anyTypeOfKind :: Kind -> Type
anyTypeOfKind kind = TyConApp anyTyCon [kind]
diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp
index 764ba10..4851315 100644
--- a/compiler/prelude/primops.txt.pp
+++ b/compiler/prelude/primops.txt.pp
@@ -2437,7 +2437,7 @@ pseudoop "seq"
{ Evaluates its first argument to head normal form, and then returns its second
argument as the result. }
-primtype Any k
+primtype Any
{ The type constructor {\tt Any} is type to which you can unsafely coerce any
lifted type, and back.
@@ -2462,8 +2462,11 @@ primtype Any k
{\tt length (Any *) ([] (Any *))}
- Note that {\tt Any} is kind polymorphic, and takes a kind {\tt k} as its
- first argument. The kind of {\tt Any} is thus {\tt forall k. k -> k}.}
+ Above, we print kinds explicitly, as if with
+ {\tt -fprint-explicit-kinds}.
+
+ Note that {\tt Any} is kind polymorphic; its kind is thus
+ {\tt forall k. k}.}
primtype AnyK
{ The kind {\tt AnyK} is the kind level counterpart to {\tt Any}. In a
More information about the ghc-commits
mailing list