[commit: testsuite] master: Add testcase for #8598 (7e5c115)
git at git.haskell.org
git at git.haskell.org
Mon Dec 9 10:13:30 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/7e5c115b88f0bae2e70f5d3fb7512c12a0f5744a/testsuite
>---------------------------------------------------------------
commit 7e5c115b88f0bae2e70f5d3fb7512c12a0f5744a
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Dec 9 10:14:00 2013 +0000
Add testcase for #8598
>---------------------------------------------------------------
7e5c115b88f0bae2e70f5d3fb7512c12a0f5744a
tests/stranal/sigs/T8598.hs | 20 ++++++++++++++++++++
tests/stranal/sigs/all.T | 1 +
2 files changed, 21 insertions(+)
diff --git a/tests/stranal/sigs/T8598.hs b/tests/stranal/sigs/T8598.hs
new file mode 100644
index 0000000..55c1a35
--- /dev/null
+++ b/tests/stranal/sigs/T8598.hs
@@ -0,0 +1,20 @@
+{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-}
+{-# LANGUAGE MagicHash , UnboxedTuples #-}
+
+module T8598(fun) where
+
+import GHC.Float (Double(..))
+import GHC.Integer (decodeDoubleInteger, encodeDoubleInteger)
+import StrAnalAnnotation (StrAnal(StrAnal))
+
+-- Float.scaleFloat for Doubles, slightly simplified
+fun :: Double -> Double
+fun x | isFix = x
+ | otherwise = case x of
+ (D# x#) -> case decodeDoubleInteger x# of
+ (# i, j #) -> D# (encodeDoubleInteger i j)
+ where
+ isFix = isDoubleFinite x == 0
+{-# ANN fun (StrAnal "<S(S),1*U(U)>m") #-}
+
+foreign import ccall unsafe "isDoubleFinite" isDoubleFinite :: Double -> Int
diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T
index 4080eb9..aee2ab3 100644
--- a/tests/stranal/sigs/all.T
+++ b/tests/stranal/sigs/all.T
@@ -18,4 +18,5 @@ test('StrAnalExample', normal, compile, ['--make -package ghc -v0 ' + config.ghc
test('T8569', expect_broken(8569), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags])
test('HyperStrUse', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags])
+test('T8598', expect_broken(8598), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags])
More information about the ghc-commits
mailing list