Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/23e7a7e09602949e4aca54795493bb32c86a1617

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

commit 23e7a7e09602949e4aca54795493bb32c86a1617
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Tue Nov 6 16:23:09 2012 +0000

    Test Trac #7386

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

 tests/ghci.debugger/scripts/T7386.hs     |   10 ++++++++++
 tests/ghci.debugger/scripts/T7386.script |    3 +++
 tests/ghci.debugger/scripts/T7386.stdout |    1 +
 tests/ghci.debugger/scripts/all.T        |    1 +
 4 files changed, 15 insertions(+), 0 deletions(-)

diff --git a/tests/ghci.debugger/scripts/T7386.hs 
b/tests/ghci.debugger/scripts/T7386.hs
new file mode 100644
index 0000000..f1e5e07
--- /dev/null
+++ b/tests/ghci.debugger/scripts/T7386.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE GADTs, DataKinds, KindSignatures, TypeFamilies, PolyKinds #-}
+
+module T7386 where
+
+data Nat = Zero | Succ Nat
+data family Sing (a :: k)
+data instance Sing (a :: Nat) where
+   SZero :: Sing Zero
+   SSucc :: Sing n -> Sing (Succ n)
+
diff --git a/tests/ghci.debugger/scripts/T7386.script 
b/tests/ghci.debugger/scripts/T7386.script
new file mode 100644
index 0000000..a8fc84a
--- /dev/null
+++ b/tests/ghci.debugger/scripts/T7386.script
@@ -0,0 +1,3 @@
+:l T7386.hs
+let x = SSucc SZero
+:f x
diff --git a/tests/ghci.debugger/scripts/T7386.stdout 
b/tests/ghci.debugger/scripts/T7386.stdout
new file mode 100644
index 0000000..376b5e8
--- /dev/null
+++ b/tests/ghci.debugger/scripts/T7386.stdout
@@ -0,0 +1 @@
+x = SSucc SZero
diff --git a/tests/ghci.debugger/scripts/all.T 
b/tests/ghci.debugger/scripts/all.T
index a29d151..a78a6f2 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -86,3 +86,4 @@ test('hist001', normal, ghci_script, ['hist001.script'])
 test('2740', normal, ghci_script, ['2740.script'])
 
 test('getargs', normal, ghci_script, ['getargs.script'])
+test('T7386', normal, ghci_script, ['T7386.script'])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to