{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
module Data.ByteString.Builder.Prim.Binary (
int8
, word8
, int16BE
, int32BE
, int64BE
, word16BE
, word32BE
, word64BE
, floatBE
, doubleBE
, int16LE
, int32LE
, int64LE
, word16LE
, word32LE
, word64LE
, floatLE
, doubleLE
, intHost
, int16Host
, int32Host
, int64Host
, wordHost
, word16Host
, word32Host
, word64Host
, floatHost
, doubleHost
) where
import Data.ByteString.Builder.Prim.Internal
import Data.ByteString.Builder.Prim.Internal.Floating
import Foreign
#include "MachDeps.h"
{-# INLINE word8 #-}
word8 :: FixedPrim Word8
word8 :: FixedPrim Word8
word8 = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE word16BE #-}
word16BE :: FixedPrim Word16
#ifdef WORDS_BIGENDIAN
word16BE = word16Host
#else
word16BE :: FixedPrim Word16
word16BE = forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a
fixedPrim Int
2 forall a b. (a -> b) -> a -> b
$ \Word16
w Ptr Word8
p -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word16
w Int
8) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w :: Word8)
#endif
{-# INLINE word16LE #-}
word16LE :: FixedPrim Word16
#ifdef WORDS_BIGENDIAN
word16LE = fixedPrim 2 $ \w p -> do
poke p (fromIntegral w :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftR w 8) :: Word8)
#else
word16LE :: FixedPrim Word16
word16LE = FixedPrim Word16
word16Host
#endif
{-# INLINE word32BE #-}
word32BE :: FixedPrim Word32
#ifdef WORDS_BIGENDIAN
word32BE = word32Host
#else
word32BE :: FixedPrim Word32
word32BE = forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a
fixedPrim Int
4 forall a b. (a -> b) -> a -> b
$ \Word32
w Ptr Word8
p -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word32
w Int
24) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word32
w Int
16) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
2) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word32
w Int
8) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
3) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
w :: Word8)
#endif
{-# INLINE word32LE #-}
word32LE :: FixedPrim Word32
#ifdef WORDS_BIGENDIAN
word32LE = fixedPrim 4 $ \w p -> do
poke p (fromIntegral w :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftR w 8) :: Word8)
poke (p `plusPtr` 2) (fromIntegral (shiftR w 16) :: Word8)
poke (p `plusPtr` 3) (fromIntegral (shiftR w 24) :: Word8)
#else
word32LE :: FixedPrim Word32
word32LE = FixedPrim Word32
word32Host
#endif
{-# INLINE word64BE #-}
word64BE :: FixedPrim Word64
#ifdef WORDS_BIGENDIAN
word64BE = word64Host
#else
#if WORD_SIZE_IN_BITS < 64
word64BE =
fixedPrim 8 $ \w p -> do
let a = fromIntegral (shiftR w 32) :: Word32
b = fromIntegral w :: Word32
poke p (fromIntegral (shiftR a 24) :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftR a 16) :: Word8)
poke (p `plusPtr` 2) (fromIntegral (shiftR a 8) :: Word8)
poke (p `plusPtr` 3) (fromIntegral a :: Word8)
poke (p `plusPtr` 4) (fromIntegral (shiftR b 24) :: Word8)
poke (p `plusPtr` 5) (fromIntegral (shiftR b 16) :: Word8)
poke (p `plusPtr` 6) (fromIntegral (shiftR b 8) :: Word8)
poke (p `plusPtr` 7) (fromIntegral b :: Word8)
#else
word64BE :: FixedPrim Word64
word64BE = forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a
fixedPrim Int
8 forall a b. (a -> b) -> a -> b
$ \Word64
w Ptr Word8
p -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
56) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
48) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
2) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
40) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
3) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
32) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
24) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
5) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
16) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
6) (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w Int
8) :: Word8)
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
7) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w :: Word8)
#endif
#endif
{-# INLINE word64LE #-}
word64LE :: FixedPrim Word64
#ifdef WORDS_BIGENDIAN
#if WORD_SIZE_IN_BITS < 64
word64LE =
fixedPrim 8 $ \w p -> do
let b = fromIntegral (shiftR w 32) :: Word32
a = fromIntegral w :: Word32
poke (p) (fromIntegral a :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftR a 8) :: Word8)
poke (p `plusPtr` 2) (fromIntegral (shiftR a 16) :: Word8)
poke (p `plusPtr` 3) (fromIntegral (shiftR a 24) :: Word8)
poke (p `plusPtr` 4) (fromIntegral b :: Word8)
poke (p `plusPtr` 5) (fromIntegral (shiftR b 8) :: Word8)
poke (p `plusPtr` 6) (fromIntegral (shiftR b 16) :: Word8)
poke (p `plusPtr` 7) (fromIntegral (shiftR b 24) :: Word8)
#else
word64LE = fixedPrim 8 $ \w p -> do
poke p (fromIntegral w :: Word8)
poke (p `plusPtr` 1) (fromIntegral (shiftR w 8) :: Word8)
poke (p `plusPtr` 2) (fromIntegral (shiftR w 16) :: Word8)
poke (p `plusPtr` 3) (fromIntegral (shiftR w 24) :: Word8)
poke (p `plusPtr` 4) (fromIntegral (shiftR w 32) :: Word8)
poke (p `plusPtr` 5) (fromIntegral (shiftR w 40) :: Word8)
poke (p `plusPtr` 6) (fromIntegral (shiftR w 48) :: Word8)
poke (p `plusPtr` 7) (fromIntegral (shiftR w 56) :: Word8)
#endif
#else
word64LE :: FixedPrim Word64
word64LE = FixedPrim Word64
word64Host
#endif
{-# INLINE wordHost #-}
wordHost :: FixedPrim Word
wordHost :: FixedPrim Word
wordHost = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE word16Host #-}
word16Host :: FixedPrim Word16
word16Host :: FixedPrim Word16
word16Host = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE word32Host #-}
word32Host :: FixedPrim Word32
word32Host :: FixedPrim Word32
word32Host = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE word64Host #-}
word64Host :: FixedPrim Word64
word64Host :: FixedPrim Word64
word64Host = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE int8 #-}
int8 :: FixedPrim Int8
int8 :: FixedPrim Int8
int8 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word8
word8
{-# INLINE int16BE #-}
int16BE :: FixedPrim Int16
int16BE :: FixedPrim Int16
int16BE = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word16
word16BE
{-# INLINE int16LE #-}
int16LE :: FixedPrim Int16
int16LE :: FixedPrim Int16
int16LE = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word16
word16LE
{-# INLINE int32BE #-}
int32BE :: FixedPrim Int32
int32BE :: FixedPrim Int32
int32BE = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word32
word32BE
{-# INLINE int32LE #-}
int32LE :: FixedPrim Int32
int32LE :: FixedPrim Int32
int32LE = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word32
word32LE
{-# INLINE int64BE #-}
int64BE :: FixedPrim Int64
int64BE :: FixedPrim Int64
int64BE = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word64
word64BE
{-# INLINE int64LE #-}
int64LE :: FixedPrim Int64
int64LE :: FixedPrim Int64
int64LE = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word64
word64LE
{-# INLINE intHost #-}
intHost :: FixedPrim Int
intHost :: FixedPrim Int
intHost = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE int16Host #-}
int16Host :: FixedPrim Int16
int16Host :: FixedPrim Int16
int16Host = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE int32Host #-}
int32Host :: FixedPrim Int32
int32Host :: FixedPrim Int32
int32Host = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE int64Host #-}
int64Host :: FixedPrim Int64
int64Host :: FixedPrim Int64
int64Host = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE floatBE #-}
floatBE :: FixedPrim Float
floatBE :: FixedPrim Float
floatBE = FixedPrim Word32 -> FixedPrim Float
encodeFloatViaWord32F FixedPrim Word32
word32BE
{-# INLINE floatLE #-}
floatLE :: FixedPrim Float
floatLE :: FixedPrim Float
floatLE = FixedPrim Word32 -> FixedPrim Float
encodeFloatViaWord32F FixedPrim Word32
word32LE
{-# INLINE doubleBE #-}
doubleBE :: FixedPrim Double
doubleBE :: FixedPrim Double
doubleBE = FixedPrim Word64 -> FixedPrim Double
encodeDoubleViaWord64F FixedPrim Word64
word64BE
{-# INLINE doubleLE #-}
doubleLE :: FixedPrim Double
doubleLE :: FixedPrim Double
doubleLE = FixedPrim Word64 -> FixedPrim Double
encodeDoubleViaWord64F FixedPrim Word64
word64LE
{-# INLINE floatHost #-}
floatHost :: FixedPrim Float
floatHost :: FixedPrim Float
floatHost = forall a. Storable a => FixedPrim a
storableToF
{-# INLINE doubleHost #-}
doubleHost :: FixedPrim Double
doubleHost :: FixedPrim Double
doubleHost = forall a. Storable a => FixedPrim a
storableToF