[commit: ghc] master: Add regression test for #11966 (ba5114e)
git at git.haskell.org
git at git.haskell.org
Fri May 12 13:08:17 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/ba5114e310e9140f2b4987245ba1f3709c7b06ec/ghc
>---------------------------------------------------------------
commit ba5114e310e9140f2b4987245ba1f3709c7b06ec
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Fri May 12 08:57:26 2017 -0400
Add regression test for #11966
Commit a7ee2d4c4229b27af324ebac93081f692835365d fixed #11966. Here's a
regression test for it.
>---------------------------------------------------------------
ba5114e310e9140f2b4987245ba1f3709c7b06ec
testsuite/tests/dependent/should_compile/T11966.hs | 34 ++++++++++++++++++++++
testsuite/tests/dependent/should_compile/all.T | 1 +
2 files changed, 35 insertions(+)
diff --git a/testsuite/tests/dependent/should_compile/T11966.hs b/testsuite/tests/dependent/should_compile/T11966.hs
new file mode 100644
index 0000000..0262a0a
--- /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 a921743..8a9b221 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, [''])
More information about the ghc-commits
mailing list