Skip to content

Commit

Permalink
Only layout changes
Browse files Browse the repository at this point in the history
  • Loading branch information
Daniel-Diaz committed May 31, 2016
1 parent 976468b commit ef18f42
Showing 1 changed file with 2 additions and 12 deletions.
14 changes: 2 additions & 12 deletions src/Data/Binary/FloatCast.hs
@@ -1,7 +1,7 @@

{-# LANGUAGE FlexibleContexts #-}

-- | This module is a literal copy of
-- | This module was written based on
-- <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
Expand All @@ -13,42 +13,32 @@ module Data.Binary.FloatCast
, 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)

{-# INLINE floatToWord #-}


-- | Reinterpret-casts a `Word32` to a `Float`.
wordToFloat :: Word32 -> Float
wordToFloat x = runST (cast x)

{-# INLINE wordToFloat #-}


-- | Reinterpret-casts a `Double` to a `Word64`.
doubleToWord :: Double -> Word64
doubleToWord x = runST (cast x)

{-# INLINE doubleToWord #-}


-- | Reinterpret-casts a `Word64` to a `Double`.
wordToDouble :: Word64 -> Double
wordToDouble x = runST (cast x)

{-# INLINE 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
{-# INLINE cast #-}

0 comments on commit ef18f42

Please sign in to comment.