[commit: ghc] master: Test Trac #9144 (2745dfb)
git at git.haskell.org
git at git.haskell.org
Tue May 27 22:15:59 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/2745dfb56414269ea53e75136166a5ed0452b2af/ghc
>---------------------------------------------------------------
commit 2745dfb56414269ea53e75136166a5ed0452b2af
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue May 27 22:27:44 2014 +0100
Test Trac #9144
>---------------------------------------------------------------
2745dfb56414269ea53e75136166a5ed0452b2af
testsuite/tests/polykinds/T9144.hs | 34 ++++++++++++++++++++++++++++++++++
testsuite/tests/polykinds/T9144.stderr | 7 +++++++
testsuite/tests/polykinds/all.T | 1 +
3 files changed, 42 insertions(+)
diff --git a/testsuite/tests/polykinds/T9144.hs b/testsuite/tests/polykinds/T9144.hs
new file mode 100644
index 0000000..0a9ef08
--- /dev/null
+++ b/testsuite/tests/polykinds/T9144.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, GADTs, RankNTypes #-}
+
+module T9144 where
+
+import Data.Proxy
+import GHC.TypeLits
+
+data family Sing (a :: k)
+
+data SomeSing :: KProxy k -> * where
+ SomeSing :: forall (a :: k). Sing a -> SomeSing ('KProxy :: KProxy k)
+
+class kproxy ~ 'KProxy => SingKind (kproxy :: KProxy k) where
+ fromSing :: forall (a :: k). Sing a -> DemoteRep ('KProxy :: KProxy k)
+ toSing :: DemoteRep ('KProxy :: KProxy k) -> SomeSing ('KProxy :: KProxy k)
+
+type family DemoteRep (kproxy :: KProxy k) :: *
+
+data Foo = Bar Nat
+data FooTerm = BarTerm Integer
+
+data instance Sing (x :: Foo) where
+ SBar :: Sing n -> Sing (Bar n)
+
+type instance DemoteRep ('KProxy :: KProxy Nat) = Integer
+type instance DemoteRep ('KProxy :: KProxy Foo) = FooTerm
+
+instance SingKind ('KProxy :: KProxy Nat) where
+ fromSing = undefined
+ toSing = undefined
+
+instance SingKind ('KProxy :: KProxy Foo) where
+ fromSing (SBar n) = BarTerm (fromSing n)
+ toSing n = case toSing n of SomeSing n' -> SomeSing (SBar n')
diff --git a/testsuite/tests/polykinds/T9144.stderr b/testsuite/tests/polykinds/T9144.stderr
new file mode 100644
index 0000000..f2c6553
--- /dev/null
+++ b/testsuite/tests/polykinds/T9144.stderr
@@ -0,0 +1,7 @@
+
+T9144.hs:34:26:
+ Couldn't match type ‘Integer’ with ‘FooTerm’
+ Expected type: DemoteRep 'KProxy
+ Actual type: DemoteRep 'KProxy
+ In the first argument of ‘toSing’, namely ‘n’
+ In the expression: toSing n
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 96faa67..09c7254 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -101,3 +101,4 @@ test('T7481', normal, compile_fail,[''])
test('T8705', normal, compile, [''])
test('T8985', normal, compile, [''])
test('T9106', normal, compile_fail, [''])
+test('T9144', normal, compile_fail, [''])
More information about the ghc-commits
mailing list