summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/printer/Makefile6
-rw-r--r--testsuite/tests/printer/Test22765.hs61
-rw-r--r--testsuite/tests/printer/all.T3
3 files changed, 69 insertions, 1 deletions
diff --git a/testsuite/tests/printer/Makefile b/testsuite/tests/printer/Makefile
index e98cfc425c..dfe29ea25d 100644
--- a/testsuite/tests/printer/Makefile
+++ b/testsuite/tests/printer/Makefile
@@ -775,3 +775,9 @@ HsDocTy:
# See comment on pprWithDocString, this won't round trip
# $(CHECK_PPR) $(LIBDIR) HsDocTy.hs
$(CHECK_EXACT) $(LIBDIR) HsDocTy.hs
+
+.PHONY: Test22765
+Test22765:
+ $(CHECK_PPR) $(LIBDIR) Test22765.hs
+ $(CHECK_EXACT) $(LIBDIR) Test22765.hs
+
diff --git a/testsuite/tests/printer/Test22765.hs b/testsuite/tests/printer/Test22765.hs
new file mode 100644
index 0000000000..6d74470900
--- /dev/null
+++ b/testsuite/tests/printer/Test22765.hs
@@ -0,0 +1,61 @@
+{-# LANGUAGE TypeData #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE MonoLocalBinds #-}
+
+module Test22765 where
+
+import Data.Kind (Type)
+import Data.Type.Equality
+
+-- example from GHC User's Guide 6.4.10.6
+
+type data Ex :: Type where
+ MkEx :: forall a. a -> Ex
+
+type family UnEx (ex :: Ex) :: k
+type instance UnEx (MkEx x) = x
+
+-- -------------------------------------
+
+type data P = MkP
+data Prom = P
+
+-- -------------------------------------
+
+type data Nat = Zero | Succ Nat
+
+-- type level GADT
+type data Vec :: Nat -> Type -> Type where
+ VNil :: Vec Zero a
+ VCons :: a -> Vec n a -> Vec (Succ n) a
+
+type X = VCons Bool (VCons Int VNil)
+
+-- -------------------------------------
+
+type data Foo :: Type -> Type where
+ MkFoo1 :: a ~ Int => Foo a
+ MkFoo2 :: a ~~ Int => Foo a
+
+-- -------------------------------------
+
+-- splice should be equivalent to giving the declaration directly
+$( [d| type data Nat = Zero | Succ Nat |] )
+
+data Vec :: Nat -> Type -> Type where
+ VNil :: Vec Zero a
+ VCons :: a -> Vec n a -> Vec (Succ n) a
+
+instance Functor (Vec n) where
+ fmap _ VNil = VNil
+ fmap f (VCons x xs) = VCons (f x) (fmap f xs)
+
+-- -------------------------------------
+
+type data List a = Nil | Cons a (List a)
+
+type data Pair a b = MkPair a b
+
+type data Sum a b = L a | R b
diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T
index 050031c6a3..409c9f2b13 100644
--- a/testsuite/tests/printer/all.T
+++ b/testsuite/tests/printer/all.T
@@ -186,4 +186,5 @@ test('T22488', normal, ghci_script, ['T22488.script'])
test('T22488_docHead', normal, compile_and_run, ['-package ghc'])
test('T20531', extra_files(['T20531_defs.hs']), ghci_script, ['T20531.script'])
test('T20531_red_ticks', extra_files(['T20531_defs.hs']), ghci_script, ['T20531_red_ticks.script'])
-test('HsDocTy', [ignore_stderr, req_ppr_deps], makefile_test, ['HsDocTy']) \ No newline at end of file
+test('HsDocTy', [ignore_stderr, req_ppr_deps], makefile_test, ['HsDocTy'])
+test('Test22765', [ignore_stderr, req_ppr_deps], makefile_test, ['Test22765']) \ No newline at end of file