[commit: ghc] ghc-7.10: Test Trac #10148 (a818ca7)
git at git.haskell.org
git at git.haskell.org
Tue Apr 14 12:49:33 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-7.10
Link : http://ghc.haskell.org/trac/ghc/changeset/a818ca74e7670f12d95f4d8b2a7ebd67295061bf/ghc
>---------------------------------------------------------------
commit a818ca74e7670f12d95f4d8b2a7ebd67295061bf
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Apr 7 17:20:43 2015 +0100
Test Trac #10148
(cherry picked from commit eacda9244913709ed025767418468b4cfc878cf9)
>---------------------------------------------------------------
a818ca74e7670f12d95f4d8b2a7ebd67295061bf
testsuite/tests/stranal/should_run/T10148.hs | 28 ++++++++++++++++++++++
.../tests/stranal/should_run/T10148.stdout | 0
testsuite/tests/stranal/should_run/all.T | 1 +
3 files changed, 29 insertions(+)
diff --git a/testsuite/tests/stranal/should_run/T10148.hs b/testsuite/tests/stranal/should_run/T10148.hs
new file mode 100644
index 0000000..cba925e
--- /dev/null
+++ b/testsuite/tests/stranal/should_run/T10148.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE BangPatterns #-}
+module Main where
+
+import Debug.Trace
+
+data Machine = Machine (Int -> Machine) Int
+
+main :: IO ()
+main = (go 7 $ Machine (gstep (Array 99)) 8) `seq` return ()
+ where
+ go :: Int -> Machine -> Int
+ go 0 (Machine _ done) = done
+ go nq (Machine step _) = go (nq-1) $ step 0
+
+gstep :: Array Int -> Int -> Machine
+gstep m x = Machine (gstep m') (mindexA m)
+ where
+ !m' = adjustA x m
+
+data Array a = Array a
+
+adjustA :: (Show a) => Int -> Array a -> Array a
+adjustA i (Array t)
+ | i < 0 = undefined i -- not just undefined!
+ | otherwise = Array $ trace ("adj " ++ show t) $ t
+
+mindexA :: Array a -> a
+mindexA (Array v) = v
diff --git a/libraries/base/tests/IO/misc001.stdout b/testsuite/tests/stranal/should_run/T10148.stdout
similarity index 100%
copy from libraries/base/tests/IO/misc001.stdout
copy to testsuite/tests/stranal/should_run/T10148.stdout
diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T
index 2ca65b5..7f64f85 100644
--- a/testsuite/tests/stranal/should_run/all.T
+++ b/testsuite/tests/stranal/should_run/all.T
@@ -8,3 +8,4 @@ test('strun004', normal, compile_and_run, [''])
test('T2756b', normal, compile_and_run, [''])
test('T7649', normal, compile_and_run, [''])
test('T9254', normal, compile_and_run, [''])
+test('T10148', normal, compile_and_run, [''])
More information about the ghc-commits
mailing list