{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif
module Data.ByteString.Builder.Prim.Internal.Floating
    (
      
    
    encodeFloatViaWord32F
  , encodeDoubleViaWord64F
  ) where
import Foreign
import Data.ByteString.Builder.Prim.Internal
{-# INLINE encodeFloatViaWord32F #-}
encodeFloatViaWord32F :: FixedPrim Word32 -> FixedPrim Float
encodeFloatViaWord32F w32fe
  | size w32fe < sizeOf (undefined :: Float) =
      error $ "encodeFloatViaWord32F: encoding not wide enough"
  | otherwise = fixedPrim (size w32fe) $ \x op -> do
      poke (castPtr op) x
      x' <- peek (castPtr op)
      runF w32fe x' op
{-# INLINE encodeDoubleViaWord64F #-}
encodeDoubleViaWord64F :: FixedPrim Word64 -> FixedPrim Double
encodeDoubleViaWord64F w64fe
  | size w64fe < sizeOf (undefined :: Float) =
      error $ "encodeDoubleViaWord64F: encoding not wide enough"
  | otherwise = fixedPrim (size w64fe) $ \x op -> do
      poke (castPtr op) x
      x' <- peek (castPtr op)
      runF w64fe x' op