#if __GLASGOW_HASKELL__ >= 701
#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
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)
encodeIntDecimal :: Integral a => Int -> BoundedPrim a
encodeIntDecimal bound = boudedPrim bound $ c_int_dec . fromIntegral
int8Dec :: BoundedPrim Int8
int8Dec = encodeIntDecimal 4
int16Dec :: BoundedPrim Int16
int16Dec = encodeIntDecimal 6
int32Dec :: BoundedPrim Int32
int32Dec = encodeIntDecimal 11
int64Dec :: BoundedPrim Int64
int64Dec = boudedPrim 20 $ c_long_long_int_dec . fromIntegral
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)
encodeWordDecimal :: Integral a => Int -> BoundedPrim a
encodeWordDecimal bound = boudedPrim bound $ c_uint_dec . fromIntegral
word8Dec :: BoundedPrim Word8
word8Dec = encodeWordDecimal 3
word16Dec :: BoundedPrim Word16
word16Dec = encodeWordDecimal 5
word32Dec :: BoundedPrim Word32
word32Dec = encodeWordDecimal 10
word64Dec :: BoundedPrim Word64
word64Dec = boudedPrim 20 $ c_long_long_uint_dec . fromIntegral
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)
encodeWordHex :: forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex =
    boudedPrim (2 * sizeOf (undefined :: a)) $ c_uint_hex  . fromIntegral
word8Hex :: BoundedPrim Word8
word8Hex = encodeWordHex
word16Hex :: BoundedPrim Word16
word16Hex = encodeWordHex
word32Hex :: BoundedPrim Word32
word32Hex = encodeWordHex
word64Hex :: BoundedPrim Word64
word64Hex = boudedPrim 16 $ c_long_long_uint_hex . fromIntegral
wordHex :: BoundedPrim Word
wordHex = caseWordSize_32_64
    (fromIntegral >$< word32Hex)
    (fromIntegral >$< word64Hex)
word8HexFixed :: FixedPrim Word8
word8HexFixed = fixedPrim 2 $
    \x op -> poke (castPtr op) =<< encode8_as_16h lowerTable x
word16HexFixed :: FixedPrim Word16
word16HexFixed =
    (\x -> (fromIntegral $ x `shiftr_w16` 8, fromIntegral x))
      >$< pairF word8HexFixed word8HexFixed
word32HexFixed :: FixedPrim Word32
word32HexFixed =
    (\x -> (fromIntegral $ x `shiftr_w32` 16, fromIntegral x))
      >$< pairF word16HexFixed word16HexFixed
word64HexFixed :: FixedPrim Word64
word64HexFixed =
    (\x -> (fromIntegral $ x `shiftr_w64` 32, fromIntegral x))
      >$< pairF word32HexFixed word32HexFixed
int8HexFixed :: FixedPrim Int8
int8HexFixed = fromIntegral >$< word8HexFixed
int16HexFixed :: FixedPrim Int16
int16HexFixed = fromIntegral >$< word16HexFixed
int32HexFixed :: FixedPrim Int32
int32HexFixed = fromIntegral >$< word32HexFixed
int64HexFixed :: FixedPrim Int64
int64HexFixed = fromIntegral >$< word64HexFixed
floatHexFixed :: FixedPrim Float
floatHexFixed = encodeFloatViaWord32F word32HexFixed
doubleHexFixed :: FixedPrim Double
doubleHexFixed = encodeDoubleViaWord64F word64HexFixed