[commit: ghc] master: Replace endian test by 64-bit word access in T7600 (4f8e348)
git at git.haskell.org
git at git.haskell.org
Tue Apr 7 14:13:29 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/4f8e34822f18cf3d31414676f900b3714367d38e/ghc
>---------------------------------------------------------------
commit 4f8e34822f18cf3d31414676f900b3714367d38e
Author: Peter Trommler <ptrommler at acm.org>
Date: Tue Apr 7 09:08:29 2015 -0500
Replace endian test by 64-bit word access in T7600
In commit 3f30912f an include `ghcconfig.h` was added for
`WORDS_BIGENDIAN`.
Converting the floating point array to a `Word64` array avoids
using the preprocessor altogether and leads to smaller code.
Fixes #10239
Reviewed By: rwbarton, austin
Differential Revision: https://phabricator.haskell.org/D795
GHC Trac Issues: #10239
>---------------------------------------------------------------
4f8e34822f18cf3d31414676f900b3714367d38e
testsuite/tests/codeGen/should_run/T7600_A.hs | 46 +++++++--------------------
1 file changed, 12 insertions(+), 34 deletions(-)
diff --git a/testsuite/tests/codeGen/should_run/T7600_A.hs b/testsuite/tests/codeGen/should_run/T7600_A.hs
index df31b83..6338c9d 100644
--- a/testsuite/tests/codeGen/should_run/T7600_A.hs
+++ b/testsuite/tests/codeGen/should_run/T7600_A.hs
@@ -1,6 +1,5 @@
-- !!! Bug # 7600.
-- See file T7600 for main description.
-{-# LANGUAGE CPP #-}
module T7600_A (test_run) where
import Control.Monad.ST
@@ -12,8 +11,6 @@ import Numeric
import GHC.Float
-#include "ghcconfig.h"
-
-- Test run
test_run :: Float -> Double -> IO ()
test_run float_number double_number = do
@@ -41,45 +38,26 @@ widen' :: Float -> Double
{-# NOINLINE widen' #-}
widen' = float2Double
-doubleToBytes :: Double -> [Int]
-doubleToBytes d
+doubleToWord64 :: Double -> Word64
+doubleToWord64 d
= runST (do
- arr <- newArray_ ((0::Int),7)
+ arr <- newArray_ ((0::Int),0)
writeArray arr 0 d
- arr <- castDoubleToWord8Array arr
- i0 <- readArray arr 0
- i1 <- readArray arr 1
- i2 <- readArray arr 2
- i3 <- readArray arr 3
- i4 <- readArray arr 4
- i5 <- readArray arr 5
- i6 <- readArray arr 6
- i7 <- readArray arr 7
- return (map fromIntegral [i0,i1,i2,i3,i4,i5,i6,i7])
+ arr <- castDoubleToWord64Array arr
+ readArray arr 0
)
-castFloatToWord8Array :: STUArray s Int Float -> ST s (STUArray s Int Word8)
-castFloatToWord8Array = castSTUArray
+castFloatToWord64Array :: STUArray s Int Float -> ST s (STUArray s Int Word64)
+castFloatToWord64Array = castSTUArray
-castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int Word8)
-castDoubleToWord8Array = castSTUArray
+castDoubleToWord64Array :: STUArray s Int Double -> ST s (STUArray s Int Word64)
+castDoubleToWord64Array = castSTUArray
dToStr :: Double -> String
dToStr d
- = let bs = doubleToBytes d
- hex d' = case showHex d' "" of
- [] -> error "dToStr: too few hex digits for float"
- [x] -> ['0',x]
- [x,y] -> [x,y]
- _ -> error "dToStr: too many hex digits for float"
+ = let bs = doubleToWord64 d
+ hex d' = showHex d' ""
- str = map toUpper $ concat . fixEndian . (map hex) $ bs
+ str = map toUpper $ hex bs
in "0x" ++ str
-fixEndian :: [a] -> [a]
-#ifdef WORDS_BIGENDIAN
-fixEndian = id
-#else
-fixEndian = reverse
-#endif
-
More information about the ghc-commits
mailing list