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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/a27f2edfb8976185b753592fd672da79e38e2c8b

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

commit a27f2edfb8976185b753592fd672da79e38e2c8b
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Mon Sep 5 08:25:32 2011 +0100

    Test Trac #5453

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

 tests/simplCore/should_run/T5453.hs     |   21 +++++++++++++++++++++
 tests/simplCore/should_run/T5453.stdout |    1 +
 tests/simplCore/should_run/all.T        |    1 +
 3 files changed, 23 insertions(+), 0 deletions(-)

diff --git a/tests/simplCore/should_run/T5453.hs 
b/tests/simplCore/should_run/T5453.hs
new file mode 100644
index 0000000..3ea727f
--- /dev/null
+++ b/tests/simplCore/should_run/T5453.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE MagicHash #-}
+module Main where
+
+import GHC.Exts
+
+data Var = TyVar !Int Bool Bool
+         | TcTyVar Bool !Int Bool
+         | Var Bool Bool !Int
+         deriving (Show)
+
+scrut :: Var -> (Bool, String)
+scrut v = (True, case v of
+    TcTyVar {} -> "OK"
+    _ -> show v ++ show (case (case v of 
+                                 TyVar b _ _ -> b 
+                                 Var _ _ b -> b) of 
+                           I# x# -> if x# ==# 7# 
+                                    then show (I# (x# +# 1#)) 
+                                    else show (I# (x# +# 2#))))
+
+main = putStrLn $ snd (scrut (TcTyVar True 1 False))
diff --git a/tests/simplCore/should_run/T5453.stdout 
b/tests/simplCore/should_run/T5453.stdout
new file mode 100644
index 0000000..e178f82
--- /dev/null
+++ b/tests/simplCore/should_run/T5453.stdout
@@ -0,0 +1 @@
+OK
diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index 174fa18..a78db43 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -45,3 +45,4 @@ test('T3972', extra_clean(['T3972A.hi', 'T3972A.o']),
               compile_and_run,
               [''])
 test('T5315', normal, compile_and_run, [''])
+test('T5453', normal, compile_and_run, [''])



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

Reply via email to