[commit: ghc] ghc-8.0: Fix #11311 (7e58aa0)
git at git.haskell.org
git at git.haskell.org
Sat Jan 16 12:49:22 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/7e58aa08be2e58d0748c89fe7fad2c0961a35083/ghc
>---------------------------------------------------------------
commit 7e58aa08be2e58d0748c89fe7fad2c0961a35083
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Mon Jan 11 17:03:47 2016 -0500
Fix #11311
All things of kind *, including * itself, need to have a PtrRep.
Test: dependent/should_compile/T11311
(cherry picked from commit 6c07f1426e58232092043e28d56717aa489d3670)
>---------------------------------------------------------------
7e58aa08be2e58d0748c89fe7fad2c0961a35083
compiler/types/TyCon.hs | 5 +++--
testsuite/tests/dependent/should_compile/T11311.hs | 8 ++++++++
testsuite/tests/dependent/should_compile/all.T | 1 +
.../{annotations/should_compile => dependent/should_run}/Makefile | 0
testsuite/tests/dependent/should_run/T11311.hs | 8 ++++++++
testsuite/tests/dependent/should_run/all.T | 4 ++++
6 files changed, 24 insertions(+), 2 deletions(-)
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 356e2ea..0f64cf9 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -568,7 +568,7 @@ data TyCon
primTyConRep :: PrimRep,-- ^ Many primitive tycons are unboxed, but
-- some are boxed (represented by
-- pointers). This 'PrimRep' holds that
- -- information. Only relevant if tyConKind = *
+ -- information. Only relevant if tyConKind = #
isUnLifted :: Bool, -- ^ Most primitive tycons are unlifted (may
-- not contain bottom) but other are lifted,
@@ -1203,7 +1203,8 @@ mkKindTyCon :: Name -> Kind -> [Role] -> Name -> TyCon
mkKindTyCon name kind roles rep_nm
= tc
where
- tc = mkPrimTyCon' name kind roles VoidRep False (Just rep_nm)
+ tc = mkPrimTyCon' name kind roles PtrRep False (Just rep_nm)
+ -- PtrRep because kinds have kind *.
-- | Create a lifted primitive 'TyCon' such as @RealWorld@
mkLiftedPrimTyCon :: Name -> Kind -> [Role] -> PrimRep -> TyCon
diff --git a/testsuite/tests/dependent/should_compile/T11311.hs b/testsuite/tests/dependent/should_compile/T11311.hs
new file mode 100644
index 0000000..88f0e45
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T11311.hs
@@ -0,0 +1,8 @@
+module T11311 where
+
+import Data.Kind
+
+foo :: ()
+foo = (id :: * -> *) undefined `seq` ()
+
+main = print foo
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index 1063b6e..ef6dde9 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -11,3 +11,4 @@ test('mkGADTVars', normal, compile, [''])
test('TypeLevelVec',normal,compile, [''])
test('T9632', normal, compile, [''])
test('dynamic-paper', normal, compile, [''])
+test('T11311', normal, compile, [''])
diff --git a/testsuite/tests/annotations/should_compile/Makefile b/testsuite/tests/dependent/should_run/Makefile
similarity index 100%
copy from testsuite/tests/annotations/should_compile/Makefile
copy to testsuite/tests/dependent/should_run/Makefile
diff --git a/testsuite/tests/dependent/should_run/T11311.hs b/testsuite/tests/dependent/should_run/T11311.hs
new file mode 100644
index 0000000..88f0e45
--- /dev/null
+++ b/testsuite/tests/dependent/should_run/T11311.hs
@@ -0,0 +1,8 @@
+module T11311 where
+
+import Data.Kind
+
+foo :: ()
+foo = (id :: * -> *) undefined `seq` ()
+
+main = print foo
diff --git a/testsuite/tests/dependent/should_run/all.T b/testsuite/tests/dependent/should_run/all.T
new file mode 100755
index 0000000..c3b18c1
--- /dev/null
+++ b/testsuite/tests/dependent/should_run/all.T
@@ -0,0 +1,4 @@
+
+
+# test('T11311', normal, compile_and_run, [''])
+
More information about the ghc-commits
mailing list