{-# LANGUAGE ScopedTypeVariables, CPP, ForeignFunctionInterface,
MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK hide #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif
module Data.ByteString.Builder.ASCII
(
int8Dec
, int16Dec
, int32Dec
, int64Dec
, intDec
, integerDec
, word8Dec
, word16Dec
, word32Dec
, word64Dec
, wordDec
, floatDec
, doubleDec
, word8Hex
, word16Hex
, word32Hex
, word64Hex
, wordHex
, int8HexFixed
, int16HexFixed
, int32HexFixed
, int64HexFixed
, word8HexFixed
, word16HexFixed
, word32HexFixed
, word64HexFixed
, floatHexFixed
, doubleHexFixed
, byteStringHex
, lazyByteStringHex
) where
import Data.ByteString as S
import Data.ByteString.Lazy as L
import Data.ByteString.Builder.Internal (Builder)
import qualified Data.ByteString.Builder.Prim as P
import Foreign
#if defined(INTEGER_GMP)
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mappend)
# endif
import Foreign.C.Types
import qualified Data.ByteString.Builder.Prim.Internal as P
import Data.ByteString.Builder.Prim.Internal.UncheckedShifts
( caseWordSize_32_64 )
# if __GLASGOW_HASKELL__ < 710
import GHC.Num (quotRemInteger)
# endif
import GHC.Types (Int(..))
# if __GLASGOW_HASKELL__ < 611
import GHC.Integer.Internals
# else
import GHC.Integer.GMP.Internals
# endif
#endif
{-# INLINE string7 #-}
string7 :: String -> Builder
string7 = P.primMapListFixed P.char7
{-# INLINE int8Dec #-}
int8Dec :: Int8 -> Builder
int8Dec = P.primBounded P.int8Dec
{-# INLINE int16Dec #-}
int16Dec :: Int16 -> Builder
int16Dec = P.primBounded P.int16Dec
{-# INLINE int32Dec #-}
int32Dec :: Int32 -> Builder
int32Dec = P.primBounded P.int32Dec
{-# INLINE int64Dec #-}
int64Dec :: Int64 -> Builder
int64Dec = P.primBounded P.int64Dec
{-# INLINE intDec #-}
intDec :: Int -> Builder
intDec = P.primBounded P.intDec
{-# INLINE word8Dec #-}
word8Dec :: Word8 -> Builder
word8Dec = P.primBounded P.word8Dec
{-# INLINE word16Dec #-}
word16Dec :: Word16 -> Builder
word16Dec = P.primBounded P.word16Dec
{-# INLINE word32Dec #-}
word32Dec :: Word32 -> Builder
word32Dec = P.primBounded P.word32Dec
{-# INLINE word64Dec #-}
word64Dec :: Word64 -> Builder
word64Dec = P.primBounded P.word64Dec
{-# INLINE wordDec #-}
wordDec :: Word -> Builder
wordDec = P.primBounded P.wordDec
{-# INLINE floatDec #-}
floatDec :: Float -> Builder
floatDec = string7 . show
{-# INLINE doubleDec #-}
doubleDec :: Double -> Builder
doubleDec = string7 . show
{-# INLINE word8Hex #-}
word8Hex :: Word8 -> Builder
word8Hex = P.primBounded P.word8Hex
{-# INLINE word16Hex #-}
word16Hex :: Word16 -> Builder
word16Hex = P.primBounded P.word16Hex
{-# INLINE word32Hex #-}
word32Hex :: Word32 -> Builder
word32Hex = P.primBounded P.word32Hex
{-# INLINE word64Hex #-}
word64Hex :: Word64 -> Builder
word64Hex = P.primBounded P.word64Hex
{-# INLINE wordHex #-}
wordHex :: Word -> Builder
wordHex = P.primBounded P.wordHex
{-# INLINE int8HexFixed #-}
int8HexFixed :: Int8 -> Builder
int8HexFixed = P.primFixed P.int8HexFixed
{-# INLINE int16HexFixed #-}
int16HexFixed :: Int16 -> Builder
int16HexFixed = P.primFixed P.int16HexFixed
{-# INLINE int32HexFixed #-}
int32HexFixed :: Int32 -> Builder
int32HexFixed = P.primFixed P.int32HexFixed
{-# INLINE int64HexFixed #-}
int64HexFixed :: Int64 -> Builder
int64HexFixed = P.primFixed P.int64HexFixed
{-# INLINE word8HexFixed #-}
word8HexFixed :: Word8 -> Builder
word8HexFixed = P.primFixed P.word8HexFixed
{-# INLINE word16HexFixed #-}
word16HexFixed :: Word16 -> Builder
word16HexFixed = P.primFixed P.word16HexFixed
{-# INLINE word32HexFixed #-}
word32HexFixed :: Word32 -> Builder
word32HexFixed = P.primFixed P.word32HexFixed
{-# INLINE word64HexFixed #-}
word64HexFixed :: Word64 -> Builder
word64HexFixed = P.primFixed P.word64HexFixed
{-# INLINE floatHexFixed #-}
floatHexFixed :: Float -> Builder
floatHexFixed = P.primFixed P.floatHexFixed
{-# INLINE doubleHexFixed #-}
doubleHexFixed :: Double -> Builder
doubleHexFixed = P.primFixed P.doubleHexFixed
{-# NOINLINE byteStringHex #-}
byteStringHex :: S.ByteString -> Builder
byteStringHex = P.primMapByteStringFixed P.word8HexFixed
{-# NOINLINE lazyByteStringHex #-}
lazyByteStringHex :: L.ByteString -> Builder
lazyByteStringHex = P.primMapLazyByteStringFixed P.word8HexFixed
#if defined(INTEGER_GMP)
# define PAIR(a,b) (# a,b #)
maxPow10 :: Integer
maxPow10 = toInteger $ (10 :: Int) ^ caseWordSize_32_64 (9 :: Int) 18
integerDec :: Integer -> Builder
integerDec (S# i#) = intDec (I# i#)
integerDec i
| i < 0 = P.primFixed P.char8 '-' `mappend` go (-i)
| otherwise = go ( i)
where
errImpossible fun =
error $ "integerDec: " ++ fun ++ ": the impossible happened."
go :: Integer -> Builder
go n | n < maxPow10 = intDec (fromInteger n)
| otherwise =
case putH (splitf (maxPow10 * maxPow10) n) of
(x:xs) -> intDec x `mappend` P.primMapListBounded intDecPadded xs
[] -> errImpossible "integerDec: go"
splitf :: Integer -> Integer -> [Integer]
splitf pow10 n0
| pow10 > n0 = [n0]
| otherwise = splith (splitf (pow10 * pow10) n0)
where
splith [] = errImpossible "splith"
splith (n:ns) =
case n `quotRemInteger` pow10 of
PAIR(q,r) | q > 0 -> q : r : splitb ns
| otherwise -> r : splitb ns
splitb [] = []
splitb (n:ns) = case n `quotRemInteger` pow10 of
PAIR(q,r) -> q : r : splitb ns
putH :: [Integer] -> [Int]
putH [] = errImpossible "putH"
putH (n:ns) = case n `quotRemInteger` maxPow10 of
PAIR(x,y)
| q > 0 -> q : r : putB ns
| otherwise -> r : putB ns
where q = fromInteger x
r = fromInteger y
putB :: [Integer] -> [Int]
putB [] = []
putB (n:ns) = case n `quotRemInteger` maxPow10 of
PAIR(q,r) -> fromInteger q : fromInteger r : putB ns
foreign import ccall unsafe "static _hs_bytestring_int_dec_padded9"
c_int_dec_padded9 :: CInt -> Ptr Word8 -> IO ()
foreign import ccall unsafe "static _hs_bytestring_long_long_int_dec_padded18"
c_long_long_int_dec_padded18 :: CLLong -> Ptr Word8 -> IO ()
{-# INLINE intDecPadded #-}
intDecPadded :: P.BoundedPrim Int
intDecPadded = P.liftFixedToBounded $ caseWordSize_32_64
(P.fixedPrim 9 $ c_int_dec_padded9 . fromIntegral)
(P.fixedPrim 18 $ c_long_long_int_dec_padded18 . fromIntegral)
#else
integerDec :: Integer -> Builder
integerDec = string7 . show
#endif