[commit: packages/binary] master: Forgot to add the source of the new module. (ac28b9e)

git at git.haskell.org git at git.haskell.org
Sat Feb 4 21:17:38 UTC 2017


Repository : ssh://git@git.haskell.org/binary

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/ac28b9e986d4b6181516c9561ef40784444705fa

>---------------------------------------------------------------

commit ac28b9e986d4b6181516c9561ef40784444705fa
Author: Daniel Díaz <dhelta.diaz at gmail.com>
Date:   Fri May 27 12:37:30 2016 -0400

    Forgot to add the source of the new module.


>---------------------------------------------------------------

ac28b9e986d4b6181516c9561ef40784444705fa
 src/Data/Binary/FloatCast.hs | 54 ++++++++++++++++++++++++++++++++++++++++++++
 1 file changed, 54 insertions(+)

diff --git a/src/Data/Binary/FloatCast.hs b/src/Data/Binary/FloatCast.hs
new file mode 100644
index 0000000..aff3a3d
--- /dev/null
+++ b/src/Data/Binary/FloatCast.hs
@@ -0,0 +1,54 @@
+
+{-# LANGUAGE FlexibleContexts #-}
+
+-- | This module is a literal copy of
+--   <http://hackage.haskell.org/package/reinterpret-cast-0.1.0/docs/src/Data-ReinterpretCast-Internal-ImplArray.html>.
+--
+--   Implements casting via a 1-elemnt STUArray, as described in
+--   <http://stackoverflow.com/a/7002812/263061>.
+module Data.Binary.FloatCast
+  ( floatToWord
+  , wordToFloat
+  , doubleToWord
+  , wordToDouble
+  ) where
+
+
+import Data.Word (Word32, Word64)
+import Data.Array.ST (newArray, readArray, MArray, STUArray)
+import Data.Array.Unsafe (castSTUArray)
+import GHC.ST (runST, ST)
+
+
+-- | Reinterpret-casts a `Float` to a `Word32`.
+floatToWord :: Float -> Word32
+floatToWord x = runST (cast x)
+
+{-# INLINEABLE floatToWord #-}
+
+
+-- | Reinterpret-casts a `Word32` to a `Float`.
+wordToFloat :: Word32 -> Float
+wordToFloat x = runST (cast x)
+
+{-# INLINEABLE wordToFloat #-}
+
+
+-- | Reinterpret-casts a `Double` to a `Word64`.
+doubleToWord :: Double -> Word64
+doubleToWord x = runST (cast x)
+
+{-# INLINEABLE doubleToWord #-}
+
+
+-- | Reinterpret-casts a `Word64` to a `Double`.
+wordToDouble :: Word64 -> Double
+wordToDouble x = runST (cast x)
+
+{-# INLINEABLE wordToDouble #-}
+
+
+{-# INLINE cast #-}
+cast :: (MArray (STUArray s) a (ST s),
+         MArray (STUArray s) b (ST s)) => a -> ST s b
+cast x = newArray (0 :: Int, 0) x >>= castSTUArray >>= flip readArray 0



More information about the ghc-commits mailing list