summaryrefslogtreecommitdiff
path: root/testsuite/tests/dependent
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2017-05-12 08:57:26 -0400
committerRyan Scott <ryan.gl.scott@gmail.com>2017-05-12 08:57:28 -0400
commitba5114e310e9140f2b4987245ba1f3709c7b06ec (patch)
treed60faa04e6bb90088af67716f19d5a788ced07e6 /testsuite/tests/dependent
parent01af8aee30c743ab505e164ac9aa02149fbe4b9e (diff)
downloadhaskell-ba5114e310e9140f2b4987245ba1f3709c7b06ec.tar.gz
Add regression test for #11966
Commit a7ee2d4c4229b27af324ebac93081f692835365d fixed #11966. Here's a regression test for it.
Diffstat (limited to 'testsuite/tests/dependent')
-rw-r--r--testsuite/tests/dependent/should_compile/T11966.hs34
-rw-r--r--testsuite/tests/dependent/should_compile/all.T1
2 files changed, 35 insertions, 0 deletions
diff --git a/testsuite/tests/dependent/should_compile/T11966.hs b/testsuite/tests/dependent/should_compile/T11966.hs
new file mode 100644
index 0000000000..0262a0aed3
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T11966.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE TypeOperators #-}
+
+module T11966 where
+
+import Data.Kind (Type)
+import GHC.TypeLits (Symbol)
+
+-- Simplification
+type family Col (f :: k -> j) (x :: k) :: Type
+
+-- Base types
+data PGBaseType = PGInteger | PGText
+
+-- Transformations
+data Column t = Column Symbol t
+newtype Nullable t = Nullable t
+newtype HasDefault t = HasDefault t
+
+-- Interpretations
+data Expr k
+
+data Record (f :: forall k. k -> Type) =
+ Record {rX :: Col f ('Column "x" 'PGInteger)
+ ,rY :: Col f ('Column "y" ('Nullable 'PGInteger))
+ ,rZ :: Col f ('HasDefault 'PGText)}
+
+x :: Record Expr
+x = undefined
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index a921743afe..8a9b221a4e 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -21,5 +21,6 @@ test('T11711', normal, compile, [''])
test('RaeJobTalk', normal, compile, [''])
test('T11635', normal, compile, [''])
test('T11719', normal, compile, [''])
+test('T11966', normal, compile, [''])
test('T12442', normal, compile, [''])
test('T13538', normal, compile, [''])