Repository : ssh://g...@git.haskell.org/bytestring On branch : ghc-head Link : http://git.haskell.org/packages/bytestring.git/commitdiff/4cc37e85c8f4718907c9888f75666d7dd0dd4f1a
>--------------------------------------------------------------- commit 4cc37e85c8f4718907c9888f75666d7dd0dd4f1a Author: Duncan Coutts <dun...@community.haskell.org> Date: Thu Oct 3 21:25:21 2013 +0100 Remove dubious and unnecessary use of unsafeCoerce It's not needed to implement Float -> Word32. Also, include the name of tests in testBoundedProperty. >--------------------------------------------------------------- 4cc37e85c8f4718907c9888f75666d7dd0dd4f1a .../Data/ByteString/Builder/Prim/TestUtils.hs | 27 +++++--------------- 1 file changed, 7 insertions(+), 20 deletions(-) diff --git a/tests/builder/Data/ByteString/Builder/Prim/TestUtils.hs b/tests/builder/Data/ByteString/Builder/Prim/TestUtils.hs index 02b7d5f..8d93262 100644 --- a/tests/builder/Data/ByteString/Builder/Prim/TestUtils.hs +++ b/tests/builder/Data/ByteString/Builder/Prim/TestUtils.hs @@ -82,7 +82,6 @@ import Foreign #endif import System.ByteOrder -import Unsafe.Coerce (unsafeCoerce) #if defined(HAVE_TEST_FRAMEWORK) import Test.HUnit (assertBool) @@ -102,9 +101,9 @@ import Test.QuickCheck (Arbitrary(..)) testBoundedProperty :: forall a. (Arbitrary a, Show a, Bounded a) => String -> (a -> Bool) -> Test testBoundedProperty name p = testGroup name - [ testProperty "arbitrary" p - , testCase "minBound" $ assertBool "minBound" (p (minBound :: a)) - , testCase "maxBound" $ assertBool "minBound" (p (maxBound :: a)) + [ testProperty name p + , testCase (name ++ " minBound") $ assertBool "minBound" (p (minBound :: a)) + , testCase (name ++ " maxBound") $ assertBool "minBound" (p (maxBound :: a)) ] -- | Quote a 'String' nicely. @@ -355,27 +354,15 @@ float_list f = f . coerceFloatToWord32 double_list :: (Word64 -> [Word8]) -> Double -> [Word8] double_list f = f . coerceDoubleToWord64 --- Note that the following use of unsafeCoerce is not guaranteed to be --- safe on GHC 7.0 and less. The reason is probably the following ticket: --- --- http://hackage.haskell.org/trac/ghc/ticket/4092 --- --- However, that only applies if the value is loaded in a register. We --- avoid this by coercing only boxed values and ensuring that they --- remain boxed using a NOINLINE pragma. --- - --- | Super unsafe coerce a 'Float' to a 'Word32'. We have to explicitly mask --- out the higher bits in case we are working on a 64-bit machine. +-- | Convert a 'Float' to a 'Word32'. {-# NOINLINE coerceFloatToWord32 #-} coerceFloatToWord32 :: Float -> Word32 -coerceFloatToWord32 = (.&. maxBound) . unsafeCoerce +coerceFloatToWord32 x = unsafePerformIO (with x (peek . castPtr)) --- | Super unsafe coerce a 'Double' to a 'Word64'. Currently, there are no --- > 64 bit machines supported by GHC. But we just play it safe. +-- | Convert a 'Double' to a 'Word64'. {-# NOINLINE coerceDoubleToWord64 #-} coerceDoubleToWord64 :: Double -> Word64 -coerceDoubleToWord64 = (.&. maxBound) . unsafeCoerce +coerceDoubleToWord64 x = unsafePerformIO (with x (peek . castPtr)) -- | Parse a variable length encoding parseVar :: (Num a, Bits a) => [Word8] -> (a, [Word8]) _______________________________________________ ghc-commits mailing list ghc-commits@haskell.org http://www.haskell.org/mailman/listinfo/ghc-commits