[commit: ghc] ghc-8.0: testsuite: Add T11824 (73bd0a3)
git at git.haskell.org
git at git.haskell.org
Sat Apr 16 17:29:22 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/73bd0a38703b5081b14c1d01d2c6b880af125225/ghc
>---------------------------------------------------------------
commit 73bd0a38703b5081b14c1d01d2c6b880af125225
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Fri Apr 15 11:41:12 2016 +0200
testsuite: Add T11824
Test Plan: Validate
Reviewers: goldfire, austin
Reviewed By: austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2107
GHC Trac Issues: #11824
(cherry picked from commit 116088de1dc3188e82f3f79b39f8e92f30ab88d7)
>---------------------------------------------------------------
73bd0a38703b5081b14c1d01d2c6b880af125225
.../tests/{driver/rtsOpts.hs => typecheck/T11824/T11824.hs} | 1 +
testsuite/tests/typecheck/T11824/TyCon.hs | 10 ++++++++++
testsuite/tests/typecheck/T11824/Type.hs | 11 +++++++++++
testsuite/tests/typecheck/T11824/Type.hs-boot | 10 ++++++++++
.../typecheck/T11824/Unbound/Generics/LocallyNameless.hs | 11 +++++++++++
testsuite/tests/typecheck/T11824/all.T | 1 +
6 files changed, 44 insertions(+)
diff --git a/testsuite/tests/driver/rtsOpts.hs b/testsuite/tests/typecheck/T11824/T11824.hs
similarity index 72%
copy from testsuite/tests/driver/rtsOpts.hs
copy to testsuite/tests/typecheck/T11824/T11824.hs
index 0634af0..ee80e4e 100644
--- a/testsuite/tests/driver/rtsOpts.hs
+++ b/testsuite/tests/typecheck/T11824/T11824.hs
@@ -1,3 +1,4 @@
+import Type
main :: IO ()
main = return ()
diff --git a/testsuite/tests/typecheck/T11824/TyCon.hs b/testsuite/tests/typecheck/T11824/TyCon.hs
new file mode 100644
index 0000000..1d74337
--- /dev/null
+++ b/testsuite/tests/typecheck/T11824/TyCon.hs
@@ -0,0 +1,10 @@
+module TyCon where
+
+import Unbound.Generics.LocallyNameless (Alpha (..))
+import {-# SOURCE #-} Type (TyName)
+
+data AlgTyConRhs
+ = NewTyCon TyName
+
+instance Alpha AlgTyConRhs where
+ isTerm (NewTyCon nm) = isTerm nm
diff --git a/testsuite/tests/typecheck/T11824/Type.hs b/testsuite/tests/typecheck/T11824/Type.hs
new file mode 100644
index 0000000..7b0a399
--- /dev/null
+++ b/testsuite/tests/typecheck/T11824/Type.hs
@@ -0,0 +1,11 @@
+module Type where
+
+import Unbound.Generics.LocallyNameless (Alpha (..),Name)
+import TyCon
+
+data TType = VarTy
+
+type TyName = Name TType
+
+instance Alpha TType where
+ isTerm VarTy = False
diff --git a/testsuite/tests/typecheck/T11824/Type.hs-boot b/testsuite/tests/typecheck/T11824/Type.hs-boot
new file mode 100644
index 0000000..3a847b9
--- /dev/null
+++ b/testsuite/tests/typecheck/T11824/Type.hs-boot
@@ -0,0 +1,10 @@
+module Type where
+
+import Unbound.Generics.LocallyNameless (Name)
+import Data.Typeable
+
+data TType
+
+type TyName = Name TType
+
+instance Typeable TType
diff --git a/testsuite/tests/typecheck/T11824/Unbound/Generics/LocallyNameless.hs b/testsuite/tests/typecheck/T11824/Unbound/Generics/LocallyNameless.hs
new file mode 100644
index 0000000..e2c63da
--- /dev/null
+++ b/testsuite/tests/typecheck/T11824/Unbound/Generics/LocallyNameless.hs
@@ -0,0 +1,11 @@
+module Unbound.Generics.LocallyNameless where
+
+import Data.Typeable (Typeable)
+
+data Name a = Name
+
+class Alpha a where
+ isTerm :: a -> Bool
+
+instance Typeable a => Alpha (Name a) where
+ isTerm _ = False
diff --git a/testsuite/tests/typecheck/T11824/all.T b/testsuite/tests/typecheck/T11824/all.T
new file mode 100644
index 0000000..90aaa1e
--- /dev/null
+++ b/testsuite/tests/typecheck/T11824/all.T
@@ -0,0 +1 @@
+test('T11824', expect_broken(11824), compile_and_run, [''])
\ No newline at end of file
More information about the ghc-commits
mailing list