[commit: ghc] master: Test Trac #11728 (b416630f)

git at git.haskell.org git at git.haskell.org
Fri Mar 25 10:20:37 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b416630faf92b5366fcc48941fa54b87f13994f8/ghc

>---------------------------------------------------------------

commit b416630faf92b5366fcc48941fa54b87f13994f8
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Mar 25 10:22:07 2016 +0000

    Test Trac #11728


>---------------------------------------------------------------

b416630faf92b5366fcc48941fa54b87f13994f8
 testsuite/tests/ghci/scripts/T11728.hs     | 30 ++++++++++++++++++++++++++++++
 testsuite/tests/ghci/scripts/T11728.script |  1 +
 testsuite/tests/ghci/scripts/all.T         |  1 +
 3 files changed, 32 insertions(+)

diff --git a/testsuite/tests/ghci/scripts/T11728.hs b/testsuite/tests/ghci/scripts/T11728.hs
new file mode 100644
index 0000000..367a9db
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T11728.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE UndecidableInstances, PatternSynonyms, GADTs #-}
+
+module T11728 where
+
+import Data.Kind
+import Data.Int
+import GHC.TypeLits
+import Text.Show.Functions
+
+data Ty ty where
+  I  :: Ty Int
+  A  :: Ty a -> Ty [a]
+
+class    GetTy ty  where getTy :: Ty ty
+instance GetTy Int where getTy = I
+instance GetTy ty => GetTy [ty] where
+  getTy = A getTy
+
+data E a where
+  UnOp   :: Unary a b -> (E a -> E b)
+
+pattern LEN :: () => (GetTy a) => E [a] -> E Int
+pattern LEN xs <- UnOp (Un OpLen _) xs where
+        LEN xs = UnOp (Un OpLen length) xs
+
+data Unary a b where
+  Un :: (GetTy a, GetTy b) => UnOp a b -> (a -> b) -> Unary a b
+
+data UnOp a b where
+  OpLen :: GetTy a => UnOp [a] Int
diff --git a/testsuite/tests/ghci/scripts/T11728.script b/testsuite/tests/ghci/scripts/T11728.script
new file mode 100644
index 0000000..fc96b81
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T11728.script
@@ -0,0 +1 @@
+:l T11728
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index f6de93b..8fab956 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -247,3 +247,4 @@ test('T11389', req_interp, run_command, ['$MAKE -s --no-print-directory T11389']
 test('T11524a', normal, ghci_script, ['T11524a.script'])
 test('T11456', normal, ghci_script, ['T11456.script'])
 test('TypeAppData', normal, ghci_script, ['TypeAppData.script'])
+test('T11728', normal, ghci_script, ['T11728.script'])



More information about the ghc-commits mailing list