[commit: ghc] wip/ttypeable: testsuite/TypeRep: Add test for #12409 (ea5f19b)
git at git.haskell.org
git at git.haskell.org
Fri Jul 29 16:29:15 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/ea5f19b01e9a91871a0ee7667fec4609e1a18b33/ghc
>---------------------------------------------------------------
commit ea5f19b01e9a91871a0ee7667fec4609e1a18b33
Author: Ben Gamari <ben at smart-cactus.org>
Date: Tue Jul 19 10:57:48 2016 +0200
testsuite/TypeRep: Add test for #12409
>---------------------------------------------------------------
ea5f19b01e9a91871a0ee7667fec4609e1a18b33
testsuite/tests/typecheck/should_run/TypeRep.hs | 12 +++++++++++-
1 file changed, 11 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/typecheck/should_run/TypeRep.hs b/testsuite/tests/typecheck/should_run/TypeRep.hs
index 3ae9577..e466de5 100644
--- a/testsuite/tests/typecheck/should_run/TypeRep.hs
+++ b/testsuite/tests/typecheck/should_run/TypeRep.hs
@@ -1,5 +1,9 @@
{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
@@ -30,6 +34,12 @@ main = do
print $ rep @Bool
print $ rep @Ordering
print $ rep @(Int -> Int)
+ print $ rep @((Eq Int, Eq String) :: Constraint)
+
+ -- Unboxed things (#12049)
+ print $ rep @Int#
+ print $ rep @(##)
+ print $ rep @(# Int#, Int #)
-- Various instantiations of a kind-polymorphic type
print $ rep @(Proxy (Eq Int))
@@ -45,4 +55,4 @@ main = do
print $ rep @(Proxy 'PtrRepLifted)
-- Something lifted and primitive
- print $ rep @RealWorld
+ print $ rep @RealWorld -- #12132
More information about the ghc-commits
mailing list