|
1 | | -{-# LANGUAGE ScopedTypeVariables #-} |
2 | | -{-# LANGUAGE Trustworthy #-} |
| 1 | +{-# LANGUAGE CPP #-} |
| 2 | + |
| 3 | +#include "MachDeps.h" |
| 4 | +#include "bytestring-cpp-macros.h" |
| 5 | + |
3 | 6 | -- | |
4 | 7 | -- Copyright : (c) 2010 Simon Meier |
5 | 8 | -- |
|
12 | 15 | -- Conversion of 'Float's and 'Double's to 'Word32's and 'Word64's. |
13 | 16 | -- |
14 | 17 | module Data.ByteString.Builder.Prim.Internal.Floating |
15 | | - ( |
16 | | - -- coerceFloatToWord32 |
17 | | - -- , coerceDoubleToWord64 |
18 | | - encodeFloatViaWord32F |
| 18 | + ( castFloatToWord32 |
| 19 | + , castDoubleToWord64 |
| 20 | + , encodeFloatViaWord32F |
19 | 21 | , encodeDoubleViaWord64F |
20 | 22 | ) where |
21 | 23 |
|
22 | | -import Foreign |
23 | 24 | import Data.ByteString.Builder.Prim.Internal |
| 25 | +import Data.Word |
| 26 | + |
| 27 | +#if HS_CAST_FLOAT_WORD_OPS_AVAILABLE |
| 28 | +import GHC.Float (castFloatToWord32, castDoubleToWord64) |
| 29 | +#else |
| 30 | +import Foreign.Marshal.Utils |
| 31 | +import Foreign.Storable |
| 32 | +import Foreign.Ptr |
24 | 33 |
|
| 34 | +import Data.ByteString.Internal.Type (unsafeDupablePerformIO) |
25 | 35 | {- |
26 | | -We work around ticket http://ghc.haskell.org/trac/ghc/ticket/4092 using the |
27 | | -FFI to store the Float/Double in the buffer and peek it out again from there. |
| 36 | +We work around ticket http://ghc.haskell.org/trac/ghc/ticket/4092 by |
| 37 | +storing the Float/Double in a temp buffer and peeking it out again from there. |
28 | 38 | -} |
29 | 39 |
|
| 40 | +-- | Interpret a 'Float' as a 'Word32' as if through a bit-for-bit copy. |
| 41 | +-- (fallback if not available through GHC.Float) |
| 42 | +-- |
| 43 | +-- e.g |
| 44 | +-- |
| 45 | +-- > showHex (castFloatToWord32 1.0) [] = "3f800000" |
| 46 | +{-# NOINLINE castFloatToWord32 #-} |
| 47 | +castFloatToWord32 :: Float -> Word32 |
| 48 | +#if (SIZEOF_HSFLOAT != SIZEOF_WORD32) || (ALIGNMENT_HSFLOAT < ALIGNMENT_WORD32) |
| 49 | + #error "don't know how to cast Float to Word32" |
| 50 | +#endif |
| 51 | +castFloatToWord32 x = unsafeDupablePerformIO (with x (peek . castPtr)) |
30 | 52 |
|
31 | | --- | Encode a 'Float' using a 'Word32' encoding. |
| 53 | +-- | Interpret a 'Double' as a 'Word64' as if through a bit-for-bit copy. |
| 54 | +-- (fallback if not available through GHC.Float) |
32 | 55 | -- |
33 | | --- PRE: The 'Word32' encoding must have a size of at least 4 bytes. |
| 56 | +-- e.g |
| 57 | +-- |
| 58 | +-- > showHex (castDoubleToWord64 1.0) [] = "3ff0000000000000" |
| 59 | +{-# NOINLINE castDoubleToWord64 #-} |
| 60 | +castDoubleToWord64 :: Double -> Word64 |
| 61 | +#if (SIZEOF_HSDOUBLE != SIZEOF_WORD64) || (ALIGNMENT_HSDOUBLE < ALIGNMENT_WORD64) |
| 62 | + #error "don't know how to cast Double to Word64" |
| 63 | +#endif |
| 64 | +castDoubleToWord64 x = unsafeDupablePerformIO (with x (peek . castPtr)) |
| 65 | +#endif |
| 66 | + |
| 67 | + |
| 68 | +-- | Encode a 'Float' using a 'Word32' encoding. |
34 | 69 | {-# INLINE encodeFloatViaWord32F #-} |
35 | 70 | encodeFloatViaWord32F :: FixedPrim Word32 -> FixedPrim Float |
36 | | -encodeFloatViaWord32F w32fe |
37 | | - | size w32fe < sizeOf (undefined :: Float) = |
38 | | - error "encodeFloatViaWord32F: encoding not wide enough" |
39 | | - | otherwise = fixedPrim (size w32fe) $ \x op -> do |
40 | | - poke (castPtr op) x |
41 | | - x' <- peek (castPtr op) |
42 | | - runF w32fe x' op |
| 71 | +#if HS_CAST_FLOAT_WORD_OPS_AVAILABLE |
| 72 | +encodeFloatViaWord32F = (castFloatToWord32 >$<) |
| 73 | +#else |
| 74 | +encodeFloatViaWord32F w32fe = fixedPrim (size w32fe) $ \x op -> do |
| 75 | + x' <- with x (peek . castPtr) |
| 76 | + runF w32fe x' op |
| 77 | +#endif |
43 | 78 |
|
44 | 79 | -- | Encode a 'Double' using a 'Word64' encoding. |
45 | | --- |
46 | | --- PRE: The 'Word64' encoding must have a size of at least 8 bytes. |
47 | 80 | {-# INLINE encodeDoubleViaWord64F #-} |
48 | 81 | encodeDoubleViaWord64F :: FixedPrim Word64 -> FixedPrim Double |
49 | | -encodeDoubleViaWord64F w64fe |
50 | | - | size w64fe < sizeOf (undefined :: Float) = |
51 | | - error "encodeDoubleViaWord64F: encoding not wide enough" |
52 | | - | otherwise = fixedPrim (size w64fe) $ \x op -> do |
53 | | - poke (castPtr op) x |
54 | | - x' <- peek (castPtr op) |
55 | | - runF w64fe x' op |
56 | | - |
| 82 | +#if HS_CAST_FLOAT_WORD_OPS_AVAILABLE |
| 83 | +encodeDoubleViaWord64F = (castDoubleToWord64 >$<) |
| 84 | +#else |
| 85 | +encodeDoubleViaWord64F w64fe = fixedPrim (size w64fe) $ \x op -> do |
| 86 | + x' <- with x (peek . castPtr) |
| 87 | + runF w64fe x' op |
| 88 | +#endif |
0 commit comments