diff options
author | Richard Eisenberg <eir@cis.upenn.edu> | 2014-10-21 10:46:27 -0400 |
---|---|---|
committer | Richard Eisenberg <eir@cis.upenn.edu> | 2014-11-01 21:12:54 -0400 |
commit | b174288b15300093a4356c853ce2ea0abb4876f5 (patch) | |
tree | 34f07e733ada7a8526ea0f2f215c9bfe30674249 /testsuite | |
parent | 2cc593dd50197c252d87321280a04f04cc173dbc (diff) | |
download | haskell-b174288b15300093a4356c853ce2ea0abb4876f5.tar.gz |
Test #8953 in th/T8953
Diffstat (limited to 'testsuite')
-rw-r--r-- | testsuite/tests/th/T8953.hs | 39 | ||||
-rw-r--r-- | testsuite/tests/th/T8953.stderr | 19 | ||||
-rw-r--r-- | testsuite/tests/th/all.T | 1 |
3 files changed, 59 insertions, 0 deletions
diff --git a/testsuite/tests/th/T8953.hs b/testsuite/tests/th/T8953.hs new file mode 100644 index 0000000000..ba5833d581 --- /dev/null +++ b/testsuite/tests/th/T8953.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TemplateHaskell, + FlexibleInstances, UndecidableInstances #-} + +module T8953 where + +import Data.Proxy +import Language.Haskell.TH +import System.IO + +type family Poly (a :: k) :: * +type instance Poly (x :: Bool) = Int +type instance Poly (x :: Maybe k) = Double + +type family Silly :: k -> * +type instance Silly = (Proxy :: * -> *) +type instance Silly = (Proxy :: (* -> *) -> *) + +a :: Proxy (Proxy :: * -> *) +b :: Proxy (Proxy :: (* -> *) -> *) +a = undefined +b = undefined + +type StarProxy (a :: *) = Proxy a + +class PC (a :: k) +instance PC (a :: *) +instance PC (Proxy :: (k -> *) -> *) + +data T1 :: k1 -> k2 -> * +data T2 :: k1 -> k2 -> * +type family F a :: k +type family G (a :: k) :: k +type instance G T1 = T2 +type instance F Char = (G T1 Bool :: (* -> *) -> *) + +$( do infos <- mapM reify [''Poly, ''Silly, 'a, 'b, ''StarProxy, ''PC, ''F, ''G] + runIO $ mapM (putStrLn . pprint) infos + runIO $ hFlush stdout + return [] ) diff --git a/testsuite/tests/th/T8953.stderr b/testsuite/tests/th/T8953.stderr new file mode 100644 index 0000000000..14db2b7f81 --- /dev/null +++ b/testsuite/tests/th/T8953.stderr @@ -0,0 +1,19 @@ +type family T8953.Poly (a_0 :: k_1) :: * +type instance T8953.Poly (x_2 :: GHC.Types.Bool) = GHC.Types.Int +type instance T8953.Poly (x_3 :: GHC.Base.Maybe k_4) = GHC.Types.Double +type family T8953.Silly :: k_0 -> * +type instance T8953.Silly = Data.Proxy.Proxy :: * -> * +type instance T8953.Silly = Data.Proxy.Proxy :: (* -> *) -> * +T8953.a :: Data.Proxy.Proxy (Data.Proxy.Proxy :: * -> *) +T8953.b :: Data.Proxy.Proxy (Data.Proxy.Proxy :: (* -> *) -> *) +type T8953.StarProxy (a_0 :: *) = Data.Proxy.Proxy a_0 +class T8953.PC (a_0 :: k_1) +instance T8953.PC (a_2 :: *) +instance T8953.PC (Data.Proxy.Proxy :: (k_3 -> *) -> *) +type family T8953.F (a_0 :: *) :: k_1 +type instance T8953.F GHC.Types.Char = T8953.G (T8953.T1 :: * -> + (* -> *) -> *) + GHC.Types.Bool :: (* -> *) -> * +type family T8953.G (a_0 :: k_1) :: k_1 +type instance T8953.G (T8953.T1 :: k_2 -> + k1_3 -> *) = T8953.T2 :: k_2 -> k1_3 -> * diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index d3ae4e4430..28ae4fb486 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -332,3 +332,4 @@ test('T7241', normal, compile_fail, ['-v0']) test('T9262', normal, compile, ['-v0']) test('T9199', normal, compile, ['-v0']) test('T9692', normal, compile, ['-v0']) +test('T8953', normal, compile, ['-v0']) |