1
1
{-# LANGUAGE ScopedTypeVariables, ExplicitForAll #-}
2
2
{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}
3
+ {-# LANGUAGE CPP #-}
3
4
4
5
module Data.ByteString.Builder.RealFloat.Internal
5
6
( (.>>)
@@ -42,6 +43,8 @@ module Data.ByteString.Builder.RealFloat.Internal
42
43
, box
43
44
, unbox
44
45
, ByteArray (.. )
46
+ , castDoubleToWord64
47
+ , castFloatToWord32
45
48
) where
46
49
47
50
import Control.Monad (foldM )
@@ -56,6 +59,23 @@ import GHC.Word (Word8, Word32(..), Word64(..))
56
59
import Foreign.Ptr (plusPtr )
57
60
import qualified Foreign.Storable as S (poke )
58
61
62
+ #if __GLASGOW_HASKELL__ >= 802
63
+ import GHC.Float (castFloatToWord32 , castDoubleToWord64 )
64
+ #else
65
+ import System.IO.Unsafe (unsafePerformIO )
66
+ import Foreign.Marshal.Utils (with )
67
+ import Foreign.Ptr (castPtr )
68
+ import Foreign.Storable (peek )
69
+ {-# NOINLINE castFloatToWord32 #-}
70
+ castFloatToWord32 :: Float -> Word32
71
+ castFloatToWord32 x = unsafePerformIO (with x (peek . castPtr))
72
+
73
+ -- | Convert a 'Double' to a 'Word64'.
74
+ {-# NOINLINE castDoubleToWord64 #-}
75
+ castDoubleToWord64 :: Double -> Word64
76
+ castDoubleToWord64 x = unsafePerformIO (with x (peek . castPtr))
77
+ #endif
78
+
59
79
{-# INLINABLE (.>>) #-}
60
80
(.>>) :: (Bits a , Integral b ) => a -> b -> a
61
81
a .>> s = unsafeShiftR a (fromIntegral s)
0 commit comments