[commit: ghc] ghc-7.10: Test #10321 in ghci/scripts/T10321 (b7287b2)

git at git.haskell.org git at git.haskell.org
Mon May 11 10:07:17 UTC 2015


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

On branch  : ghc-7.10
Link       : http://ghc.haskell.org/trac/ghc/changeset/b7287b25ac4f7c9f7190e23a068e5d72ae071651/ghc

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

commit b7287b25ac4f7c9f7190e23a068e5d72ae071651
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Thu Apr 23 16:57:34 2015 -0400

    Test #10321 in ghci/scripts/T10321
    
    (cherry picked from commit d4cf5591e51e2b91b3877a05f8153db1f5328994)


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

b7287b25ac4f7c9f7190e23a068e5d72ae071651
 testsuite/tests/ghci/scripts/T10321.hs     | 14 ++++++++++++++
 testsuite/tests/ghci/scripts/T10321.script |  2 ++
 testsuite/tests/ghci/scripts/all.T         |  2 ++
 3 files changed, 18 insertions(+)

diff --git a/testsuite/tests/ghci/scripts/T10321.hs b/testsuite/tests/ghci/scripts/T10321.hs
new file mode 100644
index 0000000..44d264a
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T10321.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE DataKinds      #-}
+{-# LANGUAGE GADTs          #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE TypeOperators  #-}
+
+module T10321 where
+
+import GHC.TypeLits
+
+data Vec :: Nat -> * -> * where
+  Nil  :: Vec 0 a
+  (:>) :: a -> Vec n a -> Vec (n + 1) a
+
+infixr 5 :>
diff --git a/testsuite/tests/ghci/scripts/T10321.script b/testsuite/tests/ghci/scripts/T10321.script
new file mode 100644
index 0000000..1ec4792
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T10321.script
@@ -0,0 +1,2 @@
+:load T10321
+:t 3 :> 4 :> 5 :> Nil
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index fbcdb25..3d2fd67 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -206,3 +206,5 @@ test('T9878b',
     [ extra_run_opts('-fobject-code'),
       extra_clean(['T9878.hi','T9878.o'])],
     ghci_script, ['T9878b.script'])
+
+test('T10321', expect_broken(10321), ghci_script, ['T10321.script'])



More information about the ghc-commits mailing list