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

On branch  : master

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

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

commit ad3a119265758379079034e8e342f79fb277138f
Author: Simon Peyton Jones <[email protected]>
Date:   Thu Aug 23 16:39:02 2012 +0100

    Test Trac #7101

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

 tests/simplCore/should_run/T7101.hs                |   14 ++++++++++++++
 .../should_run/T7101.stdout}                       |    0 
 tests/simplCore/should_run/all.T                   |    2 +-
 3 files changed, 15 insertions(+), 1 deletions(-)

diff --git a/tests/simplCore/should_run/T7101.hs 
b/tests/simplCore/should_run/T7101.hs
new file mode 100644
index 0000000..d6f22b5
--- /dev/null
+++ b/tests/simplCore/should_run/T7101.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE ImplicitParams, RankNTypes #-}
+
+module Main where
+
+f :: (?x :: Int) => ((?x :: Int) => Int) -> Bool -> Int  
+f g False = g  
+f g True = let ?x = ?x + 1
+           in f g False
+
+h :: (?x :: Int) => Int
+h = ?x
+
+main :: IO ()
+main = print (let ?x = 0 in f h True)
diff --git a/tests/codeGen/should_run/5149.stdout 
b/tests/simplCore/should_run/T7101.stdout
similarity index 100%
copy from tests/codeGen/should_run/5149.stdout
copy to tests/simplCore/should_run/T7101.stdout
diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index 210618a..fc59a0a 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -56,4 +56,4 @@ test('T5587', [ only_ways(['normal','optasm']), exit_code(1) 
], compile_and_run,
 test('T5915', only_ways(['normal','optasm']), compile_and_run, [''])
 test('T5920', only_ways(['normal','optasm']), compile_and_run, [''])
 test('T5997', normal, compile_and_run, [''])
-
+test('T7101', normal, compile_and_run, [''])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to