summaryrefslogtreecommitdiff
path: root/testsuite/tests/th/TH_reifyExplicitForAllFams.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/th/TH_reifyExplicitForAllFams.hs')
-rw-r--r--testsuite/tests/th/TH_reifyExplicitForAllFams.hs35
1 files changed, 35 insertions, 0 deletions
diff --git a/testsuite/tests/th/TH_reifyExplicitForAllFams.hs b/testsuite/tests/th/TH_reifyExplicitForAllFams.hs
new file mode 100644
index 0000000000..60a6d4563f
--- /dev/null
+++ b/testsuite/tests/th/TH_reifyExplicitForAllFams.hs
@@ -0,0 +1,35 @@
+-- test reification of explicit foralls in type families
+
+{-# LANGUAGE TypeFamilies, ExplicitForAll #-}
+module TH_reifyExplicitForAllFams where
+
+import System.IO
+import Language.Haskell.TH
+import Text.PrettyPrint.HughesPJ
+
+import Data.Proxy
+import Data.Kind
+
+$([d| data family F a
+ data instance forall a. F (Maybe a) = MkF a |])
+
+$([d| class C a where
+ type G a b
+ instance forall a. C [a] where
+ type forall b. G [a] b = Proxy b |])
+
+$([d| type family H a b where
+ forall x y. H [x] (Proxy y) = Either x y
+ forall z. H z z = Maybe z |])
+
+$(return [])
+
+test :: ()
+test = $(let
+ display :: Name -> Q ()
+ display q = do { i <- reify q; runIO $ hPutStrLn stderr (pprint i) }
+ in do { display ''F
+ ; display ''C
+ ; display ''G
+ ; display ''H
+ ; [| () |] })