summaryrefslogtreecommitdiff
path: root/testsuite/tests/indexed-types/should_compile
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/indexed-types/should_compile')
-rw-r--r--testsuite/tests/indexed-types/should_compile/T14111.hs24
-rw-r--r--testsuite/tests/indexed-types/should_compile/T8707.hs11
-rw-r--r--testsuite/tests/indexed-types/should_compile/all.T2
3 files changed, 37 insertions, 0 deletions
diff --git a/testsuite/tests/indexed-types/should_compile/T14111.hs b/testsuite/tests/indexed-types/should_compile/T14111.hs
new file mode 100644
index 0000000000..d1af549187
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T14111.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE MagicHash, UnboxedSums, NoImplicitPrelude #-}
+{-# LANGUAGE TypeFamilies #-}
+-- {-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE FunctionalDependencies #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE GADTs ,ExplicitNamespaces#-}
+{-# LANGUAGE UnboxedTuples #-}
+
+module T14111 where
+
+import GHC.Exts
+import GHC.Types
+import Prelude (undefined)
+import Data.Kind
+import Data.Void
+
+data family Maybe(x :: TYPE (r :: RuntimeRep))
+
+data instance Maybe (a :: Type ) where
+ MaybeSum :: (# a | (# #) #) -> Maybe a
+
+data instance Maybe (x :: TYPE 'UnliftedRep) where
+ MaybeSumU :: (# x | (# #) #) -> Maybe x
diff --git a/testsuite/tests/indexed-types/should_compile/T8707.hs b/testsuite/tests/indexed-types/should_compile/T8707.hs
new file mode 100644
index 0000000000..379fe068b2
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T8707.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, GADTs #-}
+
+module T8707 where
+
+import Data.Kind
+
+data family SingDF (a :: (k, k2 -> Type))
+data Ctor :: k -> Type
+
+data instance SingDF (a :: (Bool, Bool -> Type)) where
+ SFalse :: SingDF '(False, Ctor)
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 285619f570..469dd915df 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -300,3 +300,5 @@ test('T18809', normal, compile, ['-O'])
test('CEqCanOccursCheck', normal, compile, [''])
test('GivenLoop', normal, compile, [''])
test('T18875', normal, compile, [''])
+test('T8707', normal, compile, ['-O'])
+test('T14111', normal, compile, ['-O'])