{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables, ForeignFunctionInterface #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif
module Data.ByteString.Builder.Prim.ASCII
(
char7
, int8Dec
, int16Dec
, int32Dec
, int64Dec
, intDec
, word8Dec
, word16Dec
, word32Dec
, word64Dec
, wordDec
, word8Hex
, word16Hex
, word32Hex
, word64Hex
, wordHex
, int8HexFixed
, int16HexFixed
, int32HexFixed
, int64HexFixed
, word8HexFixed
, word16HexFixed
, word32HexFixed
, word64HexFixed
, floatHexFixed
, doubleHexFixed
) where
import Data.ByteString.Builder.Prim.Binary
import Data.ByteString.Builder.Prim.Internal
import Data.ByteString.Builder.Prim.Internal.Floating
import Data.ByteString.Builder.Prim.Internal.Base16
import Data.ByteString.Builder.Prim.Internal.UncheckedShifts
import Data.Char (ord)
import Foreign
import Foreign.C.Types
{-# INLINE char7 #-}
char7 :: FixedPrim Char
char7 = (\c -> fromIntegral $ ord c .&. 0x7f) >$< word8
foreign import ccall unsafe "static _hs_bytestring_int_dec" c_int_dec
:: CInt -> Ptr Word8 -> IO (Ptr Word8)
foreign import ccall unsafe "static _hs_bytestring_long_long_int_dec" c_long_long_int_dec
:: CLLong -> Ptr Word8 -> IO (Ptr Word8)
{-# INLINE encodeIntDecimal #-}
encodeIntDecimal :: Integral a => Int -> BoundedPrim a
encodeIntDecimal bound = boudedPrim bound $ c_int_dec . fromIntegral
{-# INLINE int8Dec #-}
int8Dec :: BoundedPrim Int8
int8Dec = encodeIntDecimal 4
{-# INLINE int16Dec #-}
int16Dec :: BoundedPrim Int16
int16Dec = encodeIntDecimal 6
{-# INLINE int32Dec #-}
int32Dec :: BoundedPrim Int32
int32Dec = encodeIntDecimal 11
{-# INLINE int64Dec #-}
int64Dec :: BoundedPrim Int64
int64Dec = boudedPrim 20 $ c_long_long_int_dec . fromIntegral
{-# INLINE intDec #-}
intDec :: BoundedPrim Int
intDec = caseWordSize_32_64
(fromIntegral >$< int32Dec)
(fromIntegral >$< int64Dec)
foreign import ccall unsafe "static _hs_bytestring_uint_dec" c_uint_dec
:: CUInt -> Ptr Word8 -> IO (Ptr Word8)
foreign import ccall unsafe "static _hs_bytestring_long_long_uint_dec" c_long_long_uint_dec
:: CULLong -> Ptr Word8 -> IO (Ptr Word8)
{-# INLINE encodeWordDecimal #-}
encodeWordDecimal :: Integral a => Int -> BoundedPrim a
encodeWordDecimal bound = boudedPrim bound $ c_uint_dec . fromIntegral
{-# INLINE word8Dec #-}
word8Dec :: BoundedPrim Word8
word8Dec = encodeWordDecimal 3
{-# INLINE word16Dec #-}
word16Dec :: BoundedPrim Word16
word16Dec = encodeWordDecimal 5
{-# INLINE word32Dec #-}
word32Dec :: BoundedPrim Word32
word32Dec = encodeWordDecimal 10
{-# INLINE word64Dec #-}
word64Dec :: BoundedPrim Word64
word64Dec = boudedPrim 20 $ c_long_long_uint_dec . fromIntegral
{-# INLINE wordDec #-}
wordDec :: BoundedPrim Word
wordDec = caseWordSize_32_64
(fromIntegral >$< word32Dec)
(fromIntegral >$< word64Dec)
foreign import ccall unsafe "static _hs_bytestring_uint_hex" c_uint_hex
:: CUInt -> Ptr Word8 -> IO (Ptr Word8)
foreign import ccall unsafe "static _hs_bytestring_long_long_uint_hex" c_long_long_uint_hex
:: CULLong -> Ptr Word8 -> IO (Ptr Word8)
{-# INLINE encodeWordHex #-}
encodeWordHex :: forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex =
boudedPrim (2 * sizeOf (undefined :: a)) $ c_uint_hex . fromIntegral
{-# INLINE word8Hex #-}
word8Hex :: BoundedPrim Word8
word8Hex = encodeWordHex
{-# INLINE word16Hex #-}
word16Hex :: BoundedPrim Word16
word16Hex = encodeWordHex
{-# INLINE word32Hex #-}
word32Hex :: BoundedPrim Word32
word32Hex = encodeWordHex
{-# INLINE word64Hex #-}
word64Hex :: BoundedPrim Word64
word64Hex = boudedPrim 16 $ c_long_long_uint_hex . fromIntegral
{-# INLINE wordHex #-}
wordHex :: BoundedPrim Word
wordHex = caseWordSize_32_64
(fromIntegral >$< word32Hex)
(fromIntegral >$< word64Hex)
{-# INLINE word8HexFixed #-}
word8HexFixed :: FixedPrim Word8
word8HexFixed = fixedPrim 2 $
\x op -> poke (castPtr op) =<< encode8_as_16h lowerTable x
{-# INLINE word16HexFixed #-}
word16HexFixed :: FixedPrim Word16
word16HexFixed =
(\x -> (fromIntegral $ x `shiftr_w16` 8, fromIntegral x))
>$< pairF word8HexFixed word8HexFixed
{-# INLINE word32HexFixed #-}
word32HexFixed :: FixedPrim Word32
word32HexFixed =
(\x -> (fromIntegral $ x `shiftr_w32` 16, fromIntegral x))
>$< pairF word16HexFixed word16HexFixed
{-# INLINE word64HexFixed #-}
word64HexFixed :: FixedPrim Word64
word64HexFixed =
(\x -> (fromIntegral $ x `shiftr_w64` 32, fromIntegral x))
>$< pairF word32HexFixed word32HexFixed
{-# INLINE int8HexFixed #-}
int8HexFixed :: FixedPrim Int8
int8HexFixed = fromIntegral >$< word8HexFixed
{-# INLINE int16HexFixed #-}
int16HexFixed :: FixedPrim Int16
int16HexFixed = fromIntegral >$< word16HexFixed
{-# INLINE int32HexFixed #-}
int32HexFixed :: FixedPrim Int32
int32HexFixed = fromIntegral >$< word32HexFixed
{-# INLINE int64HexFixed #-}
int64HexFixed :: FixedPrim Int64
int64HexFixed = fromIntegral >$< word64HexFixed
{-# INLINE floatHexFixed #-}
floatHexFixed :: FixedPrim Float
floatHexFixed = encodeFloatViaWord32F word32HexFixed
{-# INLINE doubleHexFixed #-}
doubleHexFixed :: FixedPrim Double
doubleHexFixed = encodeDoubleViaWord64F word64HexFixed