{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
#if !(MIN_VERSION_bytestring(0,10,0))
{-# LANGUAGE TemplateHaskell #-}
#endif
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.Data.ByteString () where
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Lazy.Internal as BL
import qualified Data.ByteString.Short as SBS
import Data.ByteString.Short.Internal (ShortByteString(..))
import GHC.Exts (ByteArray#, Char(C#), Int(I#), indexCharArray#)
import TextShow.Classes (TextShow(..))
import TextShow.Data.Char ()
import TextShow.Data.List ()
#if !(MIN_VERSION_bytestring(0,10,0))
import Data.Word (Word8)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (plusPtr)
import Foreign.Storable (peek, peekByteOff)
import TextShow.TH.Internal (deriveTextShow)
#endif
data BA = BA# ByteArray#
indexCharArray :: BA -> Int -> Char
indexCharArray :: BA -> Int -> Char
indexCharArray (BA# ByteArray#
ba#) (I# Int#
i#) = Char# -> Char
C# (ByteArray# -> Int# -> Char#
indexCharArray# ByteArray#
ba# Int#
i#)
asBA :: ShortByteString -> BA
asBA :: ShortByteString -> BA
asBA (SBS ByteArray#
ba#) = ByteArray# -> BA
BA# ByteArray#
ba#
instance TextShow BS.ByteString where
{-# INLINE showb #-}
#if MIN_VERSION_bytestring(0,10,0)
showb :: ByteString -> Builder
showb = [Char] -> Builder
forall a. TextShow a => a -> Builder
showb ([Char] -> Builder)
-> (ByteString -> [Char]) -> ByteString -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Char]
BS.unpackChars
#else
showb = showb . unpackWith BS.w2c
unpackWith :: (Word8 -> a) -> BS.ByteString -> [a]
unpackWith _ (BS.PS _ _ 0) = []
unpackWith k (BS.PS ps s l) = BS.inlinePerformIO $ withForeignPtr ps $ \p ->
go (p `plusPtr` s) (l - 1) []
where
go !p !0 !acc = peek p >>= \e -> return (k e : acc)
go !p !n !acc = peekByteOff p n >>= \e -> go p (n-1) (k e : acc)
{-# INLINE unpackWith #-}
#endif
#if MIN_VERSION_bytestring(0,10,0)
instance TextShow BL.ByteString where
showb :: ByteString -> Builder
showb = [Char] -> Builder
forall a. TextShow a => a -> Builder
showb ([Char] -> Builder)
-> (ByteString -> [Char]) -> ByteString -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Char]
BL.unpackChars
{-# INLINE showb #-}
#else
$(deriveTextShow ''BL.ByteString)
#endif
instance TextShow ShortByteString where
showb :: ShortByteString -> Builder
showb = [Char] -> Builder
forall a. TextShow a => a -> Builder
showb ([Char] -> Builder)
-> (ShortByteString -> [Char]) -> ShortByteString -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Char]
unpackChars
{-# INLINE showb #-}
unpackChars :: ShortByteString -> [Char]
unpackChars :: ShortByteString -> [Char]
unpackChars ShortByteString
bs = ShortByteString -> [Char] -> [Char]
unpackAppendCharsLazy ShortByteString
bs []
unpackAppendCharsLazy :: ShortByteString -> [Char] -> [Char]
unpackAppendCharsLazy :: ShortByteString -> [Char] -> [Char]
unpackAppendCharsLazy ShortByteString
sbs [Char]
cs0 =
Int -> Int -> [Char] -> [Char]
go Int
0 (ShortByteString -> Int
SBS.length ShortByteString
sbs) [Char]
cs0
where
sz :: Int
sz = Int
100
go :: Int -> Int -> [Char] -> [Char]
go Int
off Int
len [Char]
cs
| Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
sz = ShortByteString -> Int -> Int -> [Char] -> [Char]
unpackAppendCharsStrict ShortByteString
sbs Int
off Int
len [Char]
cs
| Bool
otherwise = ShortByteString -> Int -> Int -> [Char] -> [Char]
unpackAppendCharsStrict ShortByteString
sbs Int
off Int
sz [Char]
remainder
where remainder :: [Char]
remainder = Int -> Int -> [Char] -> [Char]
go (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
sz) [Char]
cs
unpackAppendCharsStrict :: ShortByteString -> Int -> Int -> [Char] -> [Char]
!ShortByteString
sbs Int
off Int
len [Char]
cs =
Int -> Int -> [Char] -> [Char]
go (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) [Char]
cs
where
go :: Int -> Int -> [Char] -> [Char]
go !Int
sentinal !Int
i ![Char]
acc
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
sentinal = [Char]
acc
| Bool
otherwise = let !c :: Char
c = BA -> Int -> Char
indexCharArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
i
in Int -> Int -> [Char] -> [Char]
go Int
sentinal (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Char
cChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
acc)