summaryrefslogtreecommitdiff
path: root/testsuite/tests/th/T8953.hs
diff options
context:
space:
mode:
authorRichard Eisenberg <eir@cis.upenn.edu>2014-10-21 10:46:27 -0400
committerRichard Eisenberg <eir@cis.upenn.edu>2014-11-01 21:12:54 -0400
commitb174288b15300093a4356c853ce2ea0abb4876f5 (patch)
tree34f07e733ada7a8526ea0f2f215c9bfe30674249 /testsuite/tests/th/T8953.hs
parent2cc593dd50197c252d87321280a04f04cc173dbc (diff)
downloadhaskell-b174288b15300093a4356c853ce2ea0abb4876f5.tar.gz
Test #8953 in th/T8953
Diffstat (limited to 'testsuite/tests/th/T8953.hs')
-rw-r--r--testsuite/tests/th/T8953.hs39
1 files changed, 39 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 [] )