[commit: testsuite] master: Testcase for Coercible and newtype families (#8548) (8949a7c)
git at git.haskell.org
git at git.haskell.org
Fri Nov 22 18:29:49 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/8949a7cc453a7aec9bbcb752a07c140c2f15a619/testsuite
>---------------------------------------------------------------
commit 8949a7cc453a7aec9bbcb752a07c140c2f15a619
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Fri Nov 22 10:21:36 2013 +0000
Testcase for Coercible and newtype families (#8548)
>---------------------------------------------------------------
8949a7cc453a7aec9bbcb752a07c140c2f15a619
tests/typecheck/should_run/TcCoercible.hs | 9 ++++++++-
tests/typecheck/should_run/TcCoercible.stdout | 2 ++
2 files changed, 10 insertions(+), 1 deletion(-)
diff --git a/tests/typecheck/should_run/TcCoercible.hs b/tests/typecheck/should_run/TcCoercible.hs
index 855a133..e3b29af 100644
--- a/tests/typecheck/should_run/TcCoercible.hs
+++ b/tests/typecheck/should_run/TcCoercible.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE RoleAnnotations, StandaloneDeriving, FlexibleContexts, UndecidableInstances, GADTs #-}
+{-# LANGUAGE RoleAnnotations, StandaloneDeriving, FlexibleContexts, UndecidableInstances, GADTs, TypeFamilies #-}
import GHC.Prim (Coercible, coerce)
import Data.Monoid (mempty, First(First), Last())
@@ -31,6 +31,10 @@ data Oracle where Oracle :: Coercible (Fix (Either Age)) (Fix (Either Int)) =>
foo :: Oracle -> Either Age (Fix (Either Age)) -> Fix (Either Int)
foo Oracle = coerce
+-- This ensures that Coercible looks into newtype instances (#8548)
+data family Fam k
+newtype instance Fam Int = FamInt Bool deriving Show
+
main = do
print (coerce $ one :: Age)
print (coerce $ age :: Int)
@@ -58,6 +62,9 @@ main = do
print (coerce $ (FixEither (Left age) :: FixEither Age) :: Either Int (FixEither Int))
print (coerce $ (Left one :: Either Int (FixEither Age)) :: FixEither Age)
+ print (coerce $ True :: Fam Int)
+ print (coerce $ FamInt True :: Bool)
+
foo `seq` return ()
diff --git a/tests/typecheck/should_run/TcCoercible.stdout b/tests/typecheck/should_run/TcCoercible.stdout
index 7e06734..7b8071f 100644
--- a/tests/typecheck/should_run/TcCoercible.stdout
+++ b/tests/typecheck/should_run/TcCoercible.stdout
@@ -16,3 +16,5 @@ Left ()
Fix (Left ())
Left 1
FixEither (Left (Age 1))
+FamInt True
+True
More information about the ghc-commits
mailing list