{-# LANGUAGE CPP #-}{-# LANGUAGE Unsafe #-}{-# OPTIONS_HADDOCK not-home #-}{-# OPTIONS_GHC -fexpose-all-unfoldings #-}{-# LANGUAGE GeneralizedNewtypeDeriving #-}{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE UnliftedFFITypes #-}
#include "bytestring-cpp-macros.h"
-- |-- Module : Data.ByteString.Short.Internal-- Copyright : (c) Duncan Coutts 2012-2013, Julian Ospald 2022-- License : BSD-style---- Maintainer : hasufell@posteo.de-- Stability : stable-- Portability : ghc only---- Internal representation of ShortByteString--moduleData.ByteString.Short.Internal(-- * The @ShortByteString@ type and representationShortByteString (..,SBS ),-- * Introducing and eliminating 'ShortByteString'sempty ,singleton ,pack ,unpack ,fromShort ,toShort ,-- * Basic interfacesnoc ,cons ,append ,last ,tail ,uncons ,head ,init ,unsnoc ,null ,length ,-- * Transforming ShortByteStringsmap ,reverse ,intercalate ,-- * Reducing 'ShortByteString's (folds)foldl ,foldl' ,foldl1 ,foldl1' ,foldr ,foldr' ,foldr1 ,foldr1' ,-- ** Special foldsall ,any ,concat ,-- ** Generating and unfolding ShortByteStringsreplicate ,unfoldr ,unfoldrN ,-- * Substrings-- ** Breaking stringstake ,takeEnd ,takeWhileEnd ,takeWhile ,drop ,dropEnd ,dropWhile ,dropWhileEnd ,breakEnd ,break ,span ,spanEnd ,splitAt ,split ,splitWith ,stripSuffix ,stripPrefix ,-- * PredicatesisInfixOf ,isPrefixOf ,isSuffixOf ,-- ** Search for arbitrary substringsbreakSubstring ,-- * Searching ShortByteStrings-- ** Searching by equalityelem ,-- ** Searching with a predicatefind ,filter ,partition ,-- * Indexing ShortByteStringsindex ,indexMaybe ,(!?) ,elemIndex ,elemIndices ,count ,findIndex ,findIndices ,unsafeIndex ,-- * Low level operationscreateFromPtr ,copyToPtr ,-- ** Encoding validationisValidUtf8 ,-- * Low level conversions-- ** Packing 'Foreign.C.String.CString's and pointerspackCString ,packCStringLen ,-- ** Using ShortByteStrings as 'Foreign.C.String.CString'suseAsCString ,useAsCStringLen ,)whereimportData.ByteString.Internal.Type (ByteString (..),unsafeDupablePerformIO ,accursedUnutterablePerformIO ,checkedAdd ,c_elem_index ,cIsValidUtf8BASafe ,cIsValidUtf8BA )importData.Array.Byte(ByteArray(..),MutableByteArray(..))importData.Bits(FiniteBits(finiteBitSize),shiftL
#if HS_UNALIGNED_ByteArray_OPS_OK
,shiftR
#endif
,(.&.),(.|.))importData.Data(Data(..))importData.Monoid(Monoid(..))importData.Semigroup(Semigroup(..),stimesMonoid)importData.List.NonEmpty(NonEmpty(..))importData.String(IsString(..))importControl.Applicative(pure)importControl.DeepSeq(NFData)importControl.Exception(assert)importControl.Monad((>>))importForeign.C.String(CString,CStringLen)importForeign.Marshal.Alloc(allocaBytes)importForeign.Storable(pokeByteOff)importGHC.Exts(Int(I#),Int#,Ptr(Ptr),Addr#,Char(C#),State#,RealWorld,ByteArray#,MutableByteArray#,newByteArray#,byteArrayContents#,unsafeCoerce#,copyMutableByteArray#,isByteArrayPinned#,isTrue#,compareByteArrays#,sizeofByteArray#,indexWord8Array#,indexCharArray#,writeWord8Array#,unsafeFreezeByteArray#
#if HS_UNALIGNED_ByteArray_OPS_OK
,writeWord64Array#,indexWord8ArrayAsWord64#
#endif
,setByteArray#,sizeofByteArray#,indexWord8Array#,indexCharArray#,writeWord8Array#,unsafeFreezeByteArray#,touch#)importGHC.Generics(Generic)importGHC.IOhiding(unsafeDupablePerformIO)importGHC.ForeignPtr(ForeignPtr(ForeignPtr),ForeignPtrContents(PlainPtr))importGHC.ST(ST(ST),runST)importGHC.Stack.Types(HasCallStack)importGHC.WordimportPrelude(Eq(..),Ord(..),Ordering(..),Read(..),Show(..),($),($!),error,(++),(.),(||),String,userError,Bool(..),(&&),otherwise,(+),(-),fromIntegral,(*),(^),(<$>),return,Maybe(..),not,snd)importqualifiedData.ByteString.Internal.Type asBSimportqualifiedData.ListasListimportqualifiedGHC.ExtsimportqualifiedLanguage.Haskell.TH.SyntaxasTH-- | A compact representation of a 'Word8' vector.---- It has a lower memory overhead than a 'ByteString' and does not-- contribute to heap fragmentation. It can be converted to or from a-- 'ByteString' (at the cost of copying the string data). It supports very few-- other operations.--newtypeShortByteString =-- | @since 0.12.0.0ShortByteString {ShortByteString -> ByteArray
unShortByteString ::ByteArray-- ^ @since 0.12.0.0}deriving(ShortByteString -> ShortByteString -> Bool
(ShortByteString -> ShortByteString -> Bool)
-> (ShortByteString -> ShortByteString -> Bool)
-> Eq ShortByteString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShortByteString -> ShortByteString -> Bool
== :: ShortByteString -> ShortByteString -> Bool
$c/= :: ShortByteString -> ShortByteString -> Bool
/= :: ShortByteString -> ShortByteString -> Bool
Eq,(forall (m :: * -> *). Quote m => ShortByteString -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ShortByteString -> Code m ShortByteString)
-> Lift ShortByteString
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ShortByteString -> m Exp
forall (m :: * -> *).
Quote m =>
ShortByteString -> Code m ShortByteString
$clift :: forall (m :: * -> *). Quote m => ShortByteString -> m Exp
lift :: forall (m :: * -> *). Quote m => ShortByteString -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ShortByteString -> Code m ShortByteString
liftTyped :: forall (m :: * -> *).
Quote m =>
ShortByteString -> Code m ShortByteString
TH.Lift,Typeable ShortByteString
Typeable ShortByteString =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortByteString -> c ShortByteString)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortByteString)
-> (ShortByteString -> Constr)
-> (ShortByteString -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortByteString))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortByteString))
-> ((forall b. Data b => b -> b)
-> ShortByteString -> ShortByteString)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ShortByteString -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ShortByteString -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString)
-> Data ShortByteString
ShortByteString -> Constr
ShortByteString -> DataType
(forall b. Data b => b -> b) -> ShortByteString -> ShortByteString
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ShortByteString -> u
forall u. (forall d. Data d => d -> u) -> ShortByteString -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortByteString
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortByteString -> c ShortByteString
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortByteString)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortByteString)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortByteString -> c ShortByteString
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortByteString -> c ShortByteString
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortByteString
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortByteString
$ctoConstr :: ShortByteString -> Constr
toConstr :: ShortByteString -> Constr
$cdataTypeOf :: ShortByteString -> DataType
dataTypeOf :: ShortByteString -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortByteString)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortByteString)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortByteString)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortByteString)
$cgmapT :: (forall b. Data b => b -> b) -> ShortByteString -> ShortByteString
gmapT :: (forall b. Data b => b -> b) -> ShortByteString -> ShortByteString
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortByteString -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ShortByteString -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ShortByteString -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ShortByteString -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ShortByteString -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ShortByteString -> m ShortByteString
Data,(forall x. ShortByteString -> Rep ShortByteString x)
-> (forall x. Rep ShortByteString x -> ShortByteString)
-> Generic ShortByteString
forall x. Rep ShortByteString x -> ShortByteString
forall x. ShortByteString -> Rep ShortByteString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ShortByteString -> Rep ShortByteString x
from :: forall x. ShortByteString -> Rep ShortByteString x
$cto :: forall x. Rep ShortByteString x -> ShortByteString
to :: forall x. Rep ShortByteString x -> ShortByteString
Generic,ShortByteString -> ()
(ShortByteString -> ()) -> NFData ShortByteString
forall a. (a -> ()) -> NFData a
$crnf :: ShortByteString -> ()
rnf :: ShortByteString -> ()
NFData)-- | Prior to @bytestring-0.12@ 'SBS' was a genuine constructor of 'ShortByteString',-- but now it is a bundled pattern synonym, provided as a compatibility shim.patternSBS ::ByteArray#->ShortByteString pattern$mSBS :: forall {r}.
ShortByteString -> (ByteArray# -> r) -> ((# #) -> r) -> r
$bSBS :: ByteArray# -> ShortByteString
SBS x =ShortByteString (ByteArrayx ){-# COMPLETESBS #-}-- | Lexicographic order.instanceOrdShortByteString wherecompare :: ShortByteString -> ShortByteString -> Ordering
compare =ShortByteString -> ShortByteString -> Ordering
compareBytes -- Instead of deriving Semigroup / Monoid , we stick to our own implementations-- of mappend / mconcat, because they are safer with regards to overflows-- (see prop_32bitOverflow_Short_mconcat test).-- ByteArray is likely to catch up starting from GHC 9.6:-- * https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8272-- * https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9128instanceSemigroupShortByteString where<> :: ShortByteString -> ShortByteString -> ShortByteString
(<>)=ShortByteString -> ShortByteString -> ShortByteString
append sconcat :: NonEmpty ShortByteString -> ShortByteString
sconcat (ShortByteString
b :|[ShortByteString]
bs )=[ShortByteString] -> ShortByteString
concat (ShortByteString
b ShortByteString -> [ShortByteString] -> [ShortByteString]
forall a. a -> [a] -> [a]
:[ShortByteString]
bs )stimes :: forall b. Integral b => b -> ShortByteString -> ShortByteString
stimes =b -> ShortByteString -> ShortByteString
forall b a. (Integral b, Monoid a) => b -> a -> a
stimesMonoidinstanceMonoidShortByteString wheremempty :: ShortByteString
mempty=ShortByteString
empty mappend :: ShortByteString -> ShortByteString -> ShortByteString
mappend=ShortByteString -> ShortByteString -> ShortByteString
forall a. Semigroup a => a -> a -> a
(<>)mconcat :: [ShortByteString] -> ShortByteString
mconcat=[ShortByteString] -> ShortByteString
concat instanceShowShortByteString whereshowsPrec :: Int -> ShortByteString -> ShowS
showsPrec Int
p ShortByteString
ps String
r =Int -> String -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrecInt
p (ShortByteString -> String
unpackChars ShortByteString
ps )String
r instanceReadShortByteString wherereadsPrec :: Int -> ReadS ShortByteString
readsPrec Int
p String
str =[(String -> ShortByteString
packChars String
x ,String
y )|(String
x ,String
y )<-Int -> ReadS String
forall a. Read a => Int -> ReadS a
readsPrecInt
p String
str ]-- | @since 0.10.12.0instanceGHC.Exts.IsListShortByteString wheretypeItemShortByteString =Word8fromList :: [Item ShortByteString] -> ShortByteString
fromList=ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ([Word8] -> ByteArray) -> [Word8] -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Word8] -> ByteArray
[Item ByteArray] -> ByteArray
forall l. IsList l => [Item l] -> l
GHC.Exts.fromListfromListN :: Int -> [Item ShortByteString] -> ShortByteString
fromListN=(ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ([Word8] -> ByteArray) -> [Word8] -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)(([Word8] -> ByteArray) -> [Word8] -> ShortByteString)
-> (Int -> [Word8] -> ByteArray)
-> Int
-> [Word8]
-> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> [Word8] -> ByteArray
Int -> [Item ByteArray] -> ByteArray
forall l. IsList l => Int -> [Item l] -> l
GHC.Exts.fromListNtoList :: ShortByteString -> [Item ShortByteString]
toList=ByteArray -> [Word8]
ByteArray -> [Item ByteArray]
forall l. IsList l => l -> [Item l]
GHC.Exts.toList(ByteArray -> [Word8])
-> (ShortByteString -> ByteArray) -> ShortByteString -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> ByteArray
unShortByteString -- | Beware: 'fromString' truncates multi-byte characters to octets.-- e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�instanceIsStringShortByteString wherefromString :: String -> ShortByteString
fromString=String -> ShortByteString
packChars -------------------------------------------------------------------------- Simple operations-- | /O(1)/. The empty 'ShortByteString'.empty ::ShortByteString empty :: ShortByteString
empty =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
0(\MutableByteArray s
_->() -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return())-- | /O(1)/ The length of a 'ShortByteString'.length ::ShortByteString ->Intlength :: ShortByteString -> Int
length (SBS ByteArray#
barr# )=Int# -> Int
I#(ByteArray# -> Int#
sizeofByteArray#ByteArray#
barr# )-- | /O(1)/ Test whether a 'ShortByteString' is empty.null ::ShortByteString ->Boolnull :: ShortByteString -> Bool
null ShortByteString
sbs =ShortByteString -> Int
length ShortByteString
sbs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0-- | /O(1)/ 'ShortByteString' index (subscript) operator, starting from 0.---- This is a partial function, consider using 'indexMaybe' instead.index ::HasCallStack=>ShortByteString ->Int->Word8index :: HasCallStack => ShortByteString -> Int -> Word8
index ShortByteString
sbs Int
i |Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0Bool -> Bool -> Bool
&&Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<ShortByteString -> Int
length ShortByteString
sbs =ShortByteString -> Int -> Word8
unsafeIndex ShortByteString
sbs Int
i |Bool
otherwise=ShortByteString -> Int -> Word8
forall a. HasCallStack => ShortByteString -> Int -> a
indexError ShortByteString
sbs Int
i -- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:---- > 0 <= n < length bs---- @since 0.11.0.0indexMaybe ::ShortByteString ->Int->MaybeWord8indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe ShortByteString
sbs Int
i |Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0Bool -> Bool -> Bool
&&Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<ShortByteString -> Int
length ShortByteString
sbs =Word8 -> Maybe Word8
forall a. a -> Maybe a
Just(Word8 -> Maybe Word8) -> Word8 -> Maybe Word8
forall a b. (a -> b) -> a -> b
$!ShortByteString -> Int -> Word8
unsafeIndex ShortByteString
sbs Int
i |Bool
otherwise=Maybe Word8
forall a. Maybe a
Nothing{-# INLINEindexMaybe #-}-- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:---- > 0 <= n < length bs---- @since 0.11.0.0(!?) ::ShortByteString ->Int->MaybeWord8!? :: ShortByteString -> Int -> Maybe Word8
(!?) =ShortByteString -> Int -> Maybe Word8
indexMaybe {-# INLINE(!?)#-}-- | /O(1)/ Unsafe indexing without bounds checking.unsafeIndex ::ShortByteString ->Int->Word8unsafeIndex :: ShortByteString -> Int -> Word8
unsafeIndex ShortByteString
sbs =ByteArray -> Int -> Word8
indexWord8Array (ShortByteString -> ByteArray
asBA ShortByteString
sbs )indexError ::HasCallStack=>ShortByteString ->Int->a indexError :: forall a. HasCallStack => ShortByteString -> Int -> a
indexError ShortByteString
sbs Int
i =String -> String -> a
forall a. HasCallStack => String -> String -> a
moduleError String
"index"(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$String
"error in array index: "String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
showInt
i String -> ShowS
forall a. [a] -> [a] -> [a]
++String
" not in range [0.."String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
show(ShortByteString -> Int
length ShortByteString
sbs )String -> ShowS
forall a. [a] -> [a] -> [a]
++String
"]"-------------------------------------------------------------------------- Internal utilsasBA ::ShortByteString ->ByteArrayasBA :: ShortByteString -> ByteArray
asBA (ShortByteString ByteArray
ba )=ByteArray
ba create ::Int->(foralls .MutableByteArrays ->STs ())->ShortByteString create :: Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
len forall s. MutableByteArray s -> ST s ()
fill =Bool -> ShortByteString -> ShortByteString
forall a. HasCallStack => Bool -> a -> a
assert(Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0)(ShortByteString -> ShortByteString)
-> ShortByteString -> ShortByteString
forall a b. (a -> b) -> a -> b
$(forall s. ST s ShortByteString) -> ShortByteString
forall a. (forall s. ST s a) -> a
runST((forall s. ST s ShortByteString) -> ShortByteString)
-> (forall s. ST s ShortByteString) -> ShortByteString
forall a b. (a -> b) -> a -> b
$doMutableByteArray s
mba <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
len MutableByteArray s -> ST s ()
forall s. MutableByteArray s -> ST s ()
fill MutableByteArray s
mba ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ST s ByteArray -> ST s ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba {-# INLINEcreate #-}-- | Given the maximum size needed and a function to make the contents-- of a ShortByteString, createAndTrim makes the 'ShortByteString'.-- The generating function is required to return the actual final size-- (<= the maximum size) and the result value. The resulting byte array-- is realloced to this size.createAndTrim ::Int->(foralls .MutableByteArrays ->STs (Int,a ))->(ShortByteString ,a )createAndTrim :: forall a.
Int
-> (forall s. MutableByteArray s -> ST s (Int, a))
-> (ShortByteString, a)
createAndTrim Int
maxLen forall s. MutableByteArray s -> ST s (Int, a)
fill =Bool -> (ShortByteString, a) -> (ShortByteString, a)
forall a. HasCallStack => Bool -> a -> a
assert(Int
maxLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0)((ShortByteString, a) -> (ShortByteString, a))
-> (ShortByteString, a) -> (ShortByteString, a)
forall a b. (a -> b) -> a -> b
$(forall s. ST s (ShortByteString, a)) -> (ShortByteString, a)
forall a. (forall s. ST s a) -> a
runST((forall s. ST s (ShortByteString, a)) -> (ShortByteString, a))
-> (forall s. ST s (ShortByteString, a)) -> (ShortByteString, a)
forall a b. (a -> b) -> a -> b
$doMutableByteArray s
mba <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
maxLen (Int
len ,a
res )<-MutableByteArray s -> ST s (Int, a)
forall s. MutableByteArray s -> ST s (Int, a)
fill MutableByteArray s
mba ifBool -> Bool -> Bool
forall a. HasCallStack => Bool -> a -> a
assert(Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
len Bool -> Bool -> Bool
&&Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
maxLen )(Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
maxLen thendoByteArray
ba <-MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba (ShortByteString, a) -> ST s (ShortByteString, a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return(ByteArray -> ShortByteString
ShortByteString ByteArray
ba ,a
res )elsedoMutableByteArray s
mba2 <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
len MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyMutableByteArray MutableByteArray s
mba Int
0MutableByteArray s
mba2 Int
0Int
len ByteArray
ba <-MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba2 (ShortByteString, a) -> ST s (ShortByteString, a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return(ByteArray -> ShortByteString
ShortByteString ByteArray
ba ,a
res ){-# INLINEcreateAndTrim #-}createAndTrim' ::Int->(foralls .MutableByteArrays ->STs Int)->ShortByteString createAndTrim' :: Int
-> (forall s. MutableByteArray s -> ST s Int) -> ShortByteString
createAndTrim' Int
maxLen forall s. MutableByteArray s -> ST s Int
fill =Bool -> ShortByteString -> ShortByteString
forall a. HasCallStack => Bool -> a -> a
assert(Int
maxLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0)(ShortByteString -> ShortByteString)
-> ShortByteString -> ShortByteString
forall a b. (a -> b) -> a -> b
$(forall s. ST s ShortByteString) -> ShortByteString
forall a. (forall s. ST s a) -> a
runST((forall s. ST s ShortByteString) -> ShortByteString)
-> (forall s. ST s ShortByteString) -> ShortByteString
forall a b. (a -> b) -> a -> b
$doMutableByteArray s
mba <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
maxLen Int
len <-MutableByteArray s -> ST s Int
forall s. MutableByteArray s -> ST s Int
fill MutableByteArray s
mba ifBool -> Bool -> Bool
forall a. HasCallStack => Bool -> a -> a
assert(Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
len Bool -> Bool -> Bool
&&Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
maxLen )(Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
maxLen thendoByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ST s ByteArray -> ST s ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba elsedoMutableByteArray s
mba2 <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
len MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyMutableByteArray MutableByteArray s
mba Int
0MutableByteArray s
mba2 Int
0Int
len ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ST s ByteArray -> ST s ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba2 {-# INLINEcreateAndTrim' #-}-- | Like createAndTrim, but with two buffers at oncecreateAndTrim2 ::Int->Int->(foralls .MutableByteArrays ->MutableByteArrays ->STs (Int,Int))->(ShortByteString ,ShortByteString )createAndTrim2 :: Int
-> Int
-> (forall s.
MutableByteArray s -> MutableByteArray s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
createAndTrim2 Int
maxLen1 Int
maxLen2 forall s.
MutableByteArray s -> MutableByteArray s -> ST s (Int, Int)
fill =(forall s. ST s (ShortByteString, ShortByteString))
-> (ShortByteString, ShortByteString)
forall a. (forall s. ST s a) -> a
runST((forall s. ST s (ShortByteString, ShortByteString))
-> (ShortByteString, ShortByteString))
-> (forall s. ST s (ShortByteString, ShortByteString))
-> (ShortByteString, ShortByteString)
forall a b. (a -> b) -> a -> b
$doMutableByteArray s
mba1 <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
maxLen1 MutableByteArray s
mba2 <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
maxLen2 (Int
len1 ,Int
len2 )<-MutableByteArray s -> MutableByteArray s -> ST s (Int, Int)
forall s.
MutableByteArray s -> MutableByteArray s -> ST s (Int, Int)
fill MutableByteArray s
mba1 MutableByteArray s
mba2 ShortByteString
sbs1 <-Int -> Int -> MutableByteArray s -> ST s ShortByteString
forall s. Int -> Int -> MutableByteArray s -> ST s ShortByteString
freeze' Int
len1 Int
maxLen1 MutableByteArray s
mba1 ShortByteString
sbs2 <-Int -> Int -> MutableByteArray s -> ST s ShortByteString
forall s. Int -> Int -> MutableByteArray s -> ST s ShortByteString
freeze' Int
len2 Int
maxLen2 MutableByteArray s
mba2 (ShortByteString, ShortByteString)
-> ST s (ShortByteString, ShortByteString)
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure(ShortByteString
sbs1 ,ShortByteString
sbs2 )wherefreeze' ::Int->Int->MutableByteArrays ->STs ShortByteString freeze' :: forall s. Int -> Int -> MutableByteArray s -> ST s ShortByteString
freeze' Int
len Int
maxLen MutableByteArray s
mba =ifBool -> Bool -> Bool
forall a. HasCallStack => Bool -> a -> a
assert(Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
len Bool -> Bool -> Bool
&&Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
maxLen )(Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
maxLen thendoByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ST s ByteArray -> ST s ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba elsedoMutableByteArray s
mba2 <-Int -> ST s (MutableByteArray s)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
len MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyMutableByteArray MutableByteArray s
mba Int
0MutableByteArray s
mba2 Int
0Int
len ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ST s ByteArray -> ST s ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>MutableByteArray s -> ST s ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray s
mba2 {-# INLINEcreateAndTrim2 #-}isPinned ::ByteArray#->BoolisPinned :: ByteArray# -> Bool
isPinned ByteArray#
ba# =Int# -> Bool
isTrue#(ByteArray# -> Int#
isByteArrayPinned#ByteArray#
ba# )-------------------------------------------------------------------------- Conversion to and from ByteString-- | /O(n)/. Convert a 'ByteString' into a 'ShortByteString'.---- This makes a copy, so does not retain the input string.--toShort ::ByteString ->ShortByteString toShort :: ByteString -> ShortByteString
toShort !ByteString
bs =IO ShortByteString -> ShortByteString
forall a. IO a -> a
unsafeDupablePerformIO (ByteString -> IO ShortByteString
toShortIO ByteString
bs )toShortIO ::ByteString ->IOShortByteString toShortIO :: ByteString -> IO ShortByteString
toShortIO (BS ForeignPtr Word8
fptr Int
len )=doMutableByteArray RealWorld
mba <-ST RealWorld (MutableByteArray RealWorld)
-> IO (MutableByteArray RealWorld)
forall a. ST RealWorld a -> IO a
stToIO(Int -> ST RealWorld (MutableByteArray RealWorld)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
len )ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
BS.unsafeWithForeignPtrForeignPtr Word8
fptr ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\Ptr Word8
ptr ->ST RealWorld () -> IO ()
forall a. ST RealWorld a -> IO a
stToIO(Ptr Word8
-> MutableByteArray RealWorld -> Int -> Int -> ST RealWorld ()
forall a.
Ptr a
-> MutableByteArray RealWorld -> Int -> Int -> ST RealWorld ()
copyAddrToByteArray Ptr Word8
ptr MutableByteArray RealWorld
mba Int
0Int
len )ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> IO ByteArray -> IO ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>ST RealWorld ByteArray -> IO ByteArray
forall a. ST RealWorld a -> IO a
stToIO(MutableByteArray RealWorld -> ST RealWorld ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray RealWorld
mba )-- | /O(n)/. Convert a 'ShortByteString' into a 'ByteString'.--fromShort ::ShortByteString ->ByteString fromShort :: ShortByteString -> ByteString
fromShort sbs :: ShortByteString
sbs @(SBS ByteArray#
b# )|ByteArray# -> Bool
isPinned ByteArray#
b# =ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
inPlaceFp Int
len |Bool
otherwise=Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
BS.unsafeCreateFp Int
len ((ForeignPtr Word8 -> IO ()) -> ByteString)
-> (ForeignPtr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$\ForeignPtr Word8
fp ->ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
BS.unsafeWithForeignPtrForeignPtr Word8
fp ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\Ptr Word8
p ->ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
copyToPtr ShortByteString
sbs Int
0Ptr Word8
p Int
len whereinPlaceFp :: ForeignPtr Word8
inPlaceFp =Addr# -> ForeignPtrContents -> ForeignPtr Word8
forall a. Addr# -> ForeignPtrContents -> ForeignPtr a
ForeignPtr(ByteArray# -> Addr#
byteArrayContents#ByteArray#
b# )(MutableByteArray# RealWorld -> ForeignPtrContents
PlainPtr(ByteArray# -> MutableByteArray# RealWorld
forall a b. a -> b
unsafeCoerce#ByteArray#
b# ))len :: Int
len =Int# -> Int
I#(ByteArray# -> Int#
sizeofByteArray#ByteArray#
b# )-- | /O(1)/ Convert a 'Word8' into a 'ShortByteString'---- @since 0.11.3.0singleton ::Word8->ShortByteString singleton :: Word8 -> ShortByteString
singleton =\Word8
w ->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
1(\MutableByteArray s
mba ->MutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
0Word8
w )-------------------------------------------------------------------------- Packing and unpacking from lists-- | /O(n)/. Convert a list into a 'ShortByteString'pack ::[Word8]->ShortByteString pack :: [Word8] -> ShortByteString
pack =[Word8] -> ShortByteString
packBytes -- | /O(n)/. Convert a 'ShortByteString' into a list.unpack ::ShortByteString ->[Word8]unpack :: ShortByteString -> [Word8]
unpack ShortByteString
sbs =(forall b. (Word8 -> b -> b) -> b -> b) -> [Word8]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
GHC.Exts.build(ShortByteString -> (Word8 -> b -> b) -> b -> b
forall a. ShortByteString -> (Word8 -> a -> a) -> a -> a
unpackFoldr ShortByteString
sbs ){-# INLINEunpack #-}---- Have unpack fuse with good list consumers--unpackFoldr ::ShortByteString ->(Word8->a ->a )->a ->a unpackFoldr :: forall a. ShortByteString -> (Word8 -> a -> a) -> a -> a
unpackFoldr ShortByteString
sbs Word8 -> a -> a
k a
z =(Word8 -> a -> a) -> a -> ShortByteString -> a
forall a. (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr Word8 -> a -> a
k a
z ShortByteString
sbs {-# INLINE[0]unpackFoldr #-}{-# RULES"ShortByteString unpack-list"[1]forallbs .unpackFoldr bs (:)[]=unpackBytes bs #-}packChars ::[Char]->ShortByteString packChars :: String -> ShortByteString
packChars =\String
cs ->Int -> [Word8] -> ShortByteString
packLenBytes (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.lengthString
cs )((Char -> Word8) -> String -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
List.mapChar -> Word8
BS.c2w String
cs )packBytes ::[Word8]->ShortByteString packBytes :: [Word8] -> ShortByteString
packBytes =\[Word8]
ws ->Int -> [Word8] -> ShortByteString
packLenBytes ([Word8] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.length[Word8]
ws )[Word8]
ws packLenBytes ::Int->[Word8]->ShortByteString packLenBytes :: Int -> [Word8] -> ShortByteString
packLenBytes Int
len [Word8]
ws0 =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
len (\MutableByteArray s
mba ->MutableByteArray s -> Int -> [Word8] -> ST s ()
forall s. MutableByteArray s -> Int -> [Word8] -> ST s ()
go MutableByteArray s
mba Int
0[Word8]
ws0 )wherego ::MutableByteArrays ->Int->[Word8]->STs ()go :: forall s. MutableByteArray s -> Int -> [Word8] -> ST s ()
go !MutableByteArray s
_!Int
_[]=() -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return()go !MutableByteArray s
mba !Int
i (Word8
w :[Word8]
ws )=doMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
i Word8
w MutableByteArray s -> Int -> [Word8] -> ST s ()
forall s. MutableByteArray s -> Int -> [Word8] -> ST s ()
go MutableByteArray s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)[Word8]
ws -- Unpacking bytestrings into lists efficiently is a tradeoff: on the one hand-- we would like to write a tight loop that just blats the list into memory, on-- the other hand we want it to be unpacked lazily so we don't end up with a-- massive list data structure in memory.---- Our strategy is to combine both: we will unpack lazily in reasonable sized-- chunks, where each chunk is unpacked strictly.---- unpackChars does the lazy loop, while unpackAppendBytes and-- unpackAppendChars do the chunks strictly.unpackChars ::ShortByteString ->[Char]unpackChars :: ShortByteString -> String
unpackChars ShortByteString
sbs =ShortByteString -> ShowS
unpackAppendCharsLazy ShortByteString
sbs []unpackBytes ::ShortByteString ->[Word8]unpackBytes :: ShortByteString -> [Word8]
unpackBytes ShortByteString
sbs =ShortByteString -> [Word8] -> [Word8]
unpackAppendBytesLazy ShortByteString
sbs []-- Why 100 bytes you ask? Because on a 64bit machine the list we allocate-- takes just shy of 4k which seems like a reasonable amount.-- (5 words per list element, 8 bytes per word, 100 elements = 4000 bytes)unpackAppendCharsLazy ::ShortByteString ->[Char]->[Char]unpackAppendCharsLazy :: ShortByteString -> ShowS
unpackAppendCharsLazy ShortByteString
sbs =Int -> Int -> ShowS
go Int
0(ShortByteString -> Int
length ShortByteString
sbs )wheresz :: Int
sz =Int
100go :: Int -> Int -> ShowS
go Int
off Int
len String
cs |Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
sz =ShortByteString -> Int -> Int -> ShowS
unpackAppendCharsStrict ShortByteString
sbs Int
off Int
len String
cs |Bool
otherwise=ShortByteString -> Int -> Int -> ShowS
unpackAppendCharsStrict ShortByteString
sbs Int
off Int
sz String
remainder whereremainder :: String
remainder =Int -> Int -> ShowS
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz )(Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
sz )String
cs unpackAppendBytesLazy ::ShortByteString ->[Word8]->[Word8]unpackAppendBytesLazy :: ShortByteString -> [Word8] -> [Word8]
unpackAppendBytesLazy ShortByteString
sbs =Int -> Int -> [Word8] -> [Word8]
go Int
0(ShortByteString -> Int
length ShortByteString
sbs )wheresz :: Int
sz =Int
100go :: Int -> Int -> [Word8] -> [Word8]
go Int
off Int
len [Word8]
ws |Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
sz =ShortByteString -> Int -> Int -> [Word8] -> [Word8]
unpackAppendBytesStrict ShortByteString
sbs Int
off Int
len [Word8]
ws |Bool
otherwise=ShortByteString -> Int -> Int -> [Word8] -> [Word8]
unpackAppendBytesStrict ShortByteString
sbs Int
off Int
sz [Word8]
remainder whereremainder :: [Word8]
remainder =Int -> Int -> [Word8] -> [Word8]
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz )(Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
sz )[Word8]
ws -- For these unpack functions, since we're unpacking the whole list strictly we-- build up the result list in an accumulator. This means we have to build up-- the list starting at the end. So our traversal starts at the end of the-- buffer and loops down until we hit the sentinal:unpackAppendCharsStrict ::ShortByteString ->Int->Int->[Char]->[Char]!ShortByteString
sbs Int
off Int
len =Int -> Int -> ShowS
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len )wherego :: Int -> Int -> ShowS
go !Int
sentinal !Int
i String
acc |Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
sentinal =String
acc |Bool
otherwise=let!c :: Char
c =ByteArray -> Int -> Char
indexCharArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
i inInt -> Int -> ShowS
go Int
sentinal (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(Char
c Char -> ShowS
forall a. a -> [a] -> [a]
:String
acc )unpackAppendBytesStrict ::ShortByteString ->Int->Int->[Word8]->[Word8]unpackAppendBytesStrict :: ShortByteString -> Int -> Int -> [Word8] -> [Word8]
unpackAppendBytesStrict !ShortByteString
sbs Int
off Int
len =Int -> Int -> [Word8] -> [Word8]
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len )wherego :: Int -> Int -> [Word8] -> [Word8]
go !Int
sentinal !Int
i [Word8]
acc |Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
sentinal =[Word8]
acc |Bool
otherwise=let!w :: Word8
w =ByteArray -> Int -> Word8
indexWord8Array (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
i inInt -> Int -> [Word8] -> [Word8]
go Int
sentinal (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(Word8
w Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
acc )-------------------------------------------------------------------------- Eq and Ord implementationscompareBytes ::ShortByteString ->ShortByteString ->OrderingcompareBytes :: ShortByteString -> ShortByteString -> Ordering
compareBytes ShortByteString
sbs1 ShortByteString
sbs2 =let!len1 :: Int
len1 =ShortByteString -> Int
length ShortByteString
sbs1 !len2 :: Int
len2 =ShortByteString -> Int
length ShortByteString
sbs2 !len :: Int
len =Int -> Int -> Int
forall a. Ord a => a -> a -> a
minInt
len1 Int
len2 incaseByteArray -> ByteArray -> Int -> Int
compareByteArrays (ShortByteString -> ByteArray
asBA ShortByteString
sbs1 )(ShortByteString -> ByteArray
asBA ShortByteString
sbs2 )Int
len ofInt
i |Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
0->Ordering
LT|Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
0->Ordering
GT|Int
len2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
len1 ->Ordering
LT|Int
len2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
len1 ->Ordering
GT|Bool
otherwise->Ordering
EQ-------------------------------------------------------------------------- Appending and concatenationappend ::ShortByteString ->ShortByteString ->ShortByteString append :: ShortByteString -> ShortByteString -> ShortByteString
append ShortByteString
src1 ShortByteString
src2 =let!len1 :: Int
len1 =ShortByteString -> Int
length ShortByteString
src1 !len2 :: Int
len2 =ShortByteString -> Int
length ShortByteString
src2 inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create (String -> Int -> Int -> Int
checkedAdd String
"Short.append"Int
len1 Int
len2 )((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
dst ->doByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
src1 )Int
0MutableByteArray s
dst Int
0Int
len1 ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
src2 )Int
0MutableByteArray s
dst Int
len1 Int
len2 concat ::[ShortByteString ]->ShortByteString concat :: [ShortByteString] -> ShortByteString
concat =\[ShortByteString]
sbss ->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create (Int -> [ShortByteString] -> Int
totalLen Int
0[ShortByteString]
sbss )(\MutableByteArray s
dst ->MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
forall s. MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
copy MutableByteArray s
dst Int
0[ShortByteString]
sbss )wheretotalLen :: Int -> [ShortByteString] -> Int
totalLen !Int
acc []=Int
acc totalLen !Int
acc (ShortByteString
curr :[ShortByteString]
rest )=Int -> [ShortByteString] -> Int
totalLen (String -> Int -> Int -> Int
checkedAdd String
"Short.concat"Int
acc (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ShortByteString -> Int
length ShortByteString
curr )[ShortByteString]
rest copy ::MutableByteArrays ->Int->[ShortByteString ]->STs ()copy :: forall s. MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
copy !MutableByteArray s
_!Int
_[]=() -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return()copy !MutableByteArray s
dst !Int
off (ShortByteString
src :[ShortByteString]
sbss )=dolet!len :: Int
len =ShortByteString -> Int
length ShortByteString
src ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
src )Int
0MutableByteArray s
dst Int
off Int
len MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
forall s. MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
copy MutableByteArray s
dst (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len )[ShortByteString]
sbss -- ----------------------------------------------------------------------- Basic interfaceinfixr5`cons` --same as list (:)infixl5`snoc` -- | /O(n)/ Append a byte to the end of a 'ShortByteString'---- Note: copies the entire byte array---- @since 0.11.3.0snoc ::ShortByteString ->Word8->ShortByteString snoc :: ShortByteString -> Word8 -> ShortByteString
snoc =\ShortByteString
sbs Word8
c ->letlen :: Int
len =ShortByteString -> Int
length ShortByteString
sbs newLen :: Int
newLen =String -> Int -> Int -> Int
checkedAdd String
"Short.snoc"Int
len Int
1inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
newLen ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->doByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
len MutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
len Word8
c -- | /O(n)/ 'cons' is analogous to (:) for lists.---- Note: copies the entire byte array---- @since 0.11.3.0cons ::Word8->ShortByteString ->ShortByteString cons :: Word8 -> ShortByteString -> ShortByteString
cons Word8
c =\ShortByteString
sbs ->letlen :: Int
len =ShortByteString -> Int
length ShortByteString
sbs newLen :: Int
newLen =String -> Int -> Int -> Int
checkedAdd String
"Short.cons"Int
len Int
1inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
newLen ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->doMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
0Word8
c ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
1Int
len -- | /O(1)/ Extract the last element of a ShortByteString, which must be finite and non-empty.-- An exception will be thrown in the case of an empty ShortByteString.---- This is a partial function, consider using 'unsnoc' instead.---- @since 0.11.3.0last ::HasCallStack=>ShortByteString ->Word8last :: HasCallStack => ShortByteString -> Word8
last =\ShortByteString
sbs ->caseShortByteString -> Bool
null ShortByteString
sbs ofBool
True->String -> Word8
forall a. HasCallStack => String -> a
errorEmptySBS String
"last"Bool
False->ByteArray -> Int -> Word8
indexWord8Array (ShortByteString -> ByteArray
asBA ShortByteString
sbs )(ShortByteString -> Int
length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)-- | /O(n)/ Extract the elements after the head of a ShortByteString, which must be non-empty.-- An exception will be thrown in the case of an empty ShortByteString.---- This is a partial function, consider using 'uncons' instead.---- Note: copies the entire byte array---- @since 0.11.3.0tail ::HasCallStack=>ShortByteString ->ShortByteString tail :: HasCallStack => ShortByteString -> ShortByteString
tail =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs nl :: Int
nl =Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1incaseShortByteString -> Bool
null ShortByteString
sbs ofBool
True->String -> ShortByteString
forall a. HasCallStack => String -> a
errorEmptySBS String
"tail"Bool
False->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
1MutableByteArray s
mba Int
0Int
nl -- | /O(n)/ Extract the 'head' and 'tail' of a ShortByteString, returning 'Nothing'-- if it is empty.---- @since 0.11.3.0uncons ::ShortByteString ->Maybe(Word8,ShortByteString )uncons :: ShortByteString -> Maybe (Word8, ShortByteString)
uncons =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs nl :: Int
nl =Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1inif|Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->Maybe (Word8, ShortByteString)
forall a. Maybe a
Nothing|Bool
otherwise->leth :: Word8
h =ByteArray -> Int -> Word8
indexWord8Array (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0t :: ShortByteString
t =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
1MutableByteArray s
mba Int
0Int
nl in(Word8, ShortByteString) -> Maybe (Word8, ShortByteString)
forall a. a -> Maybe a
Just(Word8
h ,ShortByteString
t )-- | /O(1)/ Extract the first element of a ShortByteString, which must be non-empty.-- An exception will be thrown in the case of an empty ShortByteString.---- This is a partial function, consider using 'uncons' instead.---- @since 0.11.3.0head ::HasCallStack=>ShortByteString ->Word8head :: HasCallStack => ShortByteString -> Word8
head =\ShortByteString
sbs ->caseShortByteString -> Bool
null ShortByteString
sbs ofBool
True->String -> Word8
forall a. HasCallStack => String -> a
errorEmptySBS String
"head"Bool
False->ByteArray -> Int -> Word8
indexWord8Array (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0-- | /O(n)/ Return all the elements of a 'ShortByteString' except the last one.-- An exception will be thrown in the case of an empty ShortByteString.---- This is a partial function, consider using 'unsnoc' instead.---- Note: copies the entire byte array---- @since 0.11.3.0init ::HasCallStack=>ShortByteString ->ShortByteString init :: HasCallStack => ShortByteString -> ShortByteString
init =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs nl :: Int
nl =Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1incaseShortByteString -> Bool
null ShortByteString
sbs ofBool
True->String -> ShortByteString
forall a. HasCallStack => String -> a
errorEmptySBS String
"init"Bool
False->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
nl -- | /O(n)/ Extract the 'init' and 'last' of a ShortByteString, returning 'Nothing'-- if it is empty.---- @since 0.11.3.0unsnoc ::ShortByteString ->Maybe(ShortByteString ,Word8)unsnoc :: ShortByteString -> Maybe (ShortByteString, Word8)
unsnoc =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs nl :: Int
nl =Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1inif|Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->Maybe (ShortByteString, Word8)
forall a. Maybe a
Nothing|Bool
otherwise->letl' :: Word8
l' =ByteArray -> Int -> Word8
indexWord8Array (ShortByteString -> ByteArray
asBA ShortByteString
sbs )(Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)i :: ShortByteString
i =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
nl in(ShortByteString, Word8) -> Maybe (ShortByteString, Word8)
forall a. a -> Maybe a
Just(ShortByteString
i ,Word8
l' )-- ----------------------------------------------------------------------- Transformations-- | /O(n)/ 'map' @f xs@ is the ShortByteString obtained by applying @f@ to each-- element of @xs@.---- @since 0.11.3.0map ::(Word8->Word8)->ShortByteString ->ShortByteString map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString
map Word8 -> Word8
f =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
l (\MutableByteArray s
mba ->ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
forall s. ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
go ByteArray
ba MutableByteArray s
mba Int
0Int
l )wherego ::ByteArray->MutableByteArrays ->Int->Int->STs ()go :: forall s. ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
go !ByteArray
ba !MutableByteArray s
mba !Int
i !Int
l |Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =() -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return()|Bool
otherwise=doletw :: Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba Int
i MutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
i (Word8 -> Word8
f Word8
w )ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
forall s. ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
go ByteArray
ba MutableByteArray s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)Int
l -- | /O(n)/ 'reverse' @xs@ efficiently returns the elements of @xs@ in reverse order.---- @since 0.11.3.0reverse ::ShortByteString ->ShortByteString reverse :: ShortByteString -> ShortByteString
reverse =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs
#if HS_UNALIGNED_ByteArray_OPS_OK
inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
l (\MutableByteArray s
mba ->ByteArray -> MutableByteArray s -> Int -> ST s ()
forall s. ByteArray -> MutableByteArray s -> Int -> ST s ()
go ByteArray
ba MutableByteArray s
mba Int
l )wherego ::foralls .ByteArray->MutableByteArrays ->Int->STs ()go :: forall s. ByteArray -> MutableByteArray s -> Int -> ST s ()
go !ByteArray
ba !MutableByteArray s
mba !Int
l =do-- this is equivalent to: (q, r) = l `quotRem` 8letq :: Int
q =Int
l Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR`Int
3r :: Int
r =Int
l Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&.Int
7Int
i' <-Int -> Int -> ST s Int
goWord8Chunk Int
0Int
r Int -> Int -> Int -> ST s ()
goWord64Chunk Int
i' Int
0Int
q wheregoWord64Chunk ::Int->Int->Int->STs ()goWord64Chunk :: Int -> Int -> Int -> ST s ()
goWord64Chunk !Int
off !Int
i' !Int
cl =Int -> ST s ()
loop Int
i' whereloop ::Int->STs ()loop :: Int -> ST s ()
loop !Int
i |Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
cl =() -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return()|Bool
otherwise=doletw :: Word64
w =ByteArray -> Int -> Word64
indexWord8ArrayAsWord64 ByteArray
ba (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+(Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
8))MutableByteArray s -> Int -> Word64 -> ST s ()
forall s. MutableByteArray s -> Int -> Word64 -> ST s ()
writeWord64Array MutableByteArray s
mba (Int
cl Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i )(Word64 -> Word64
byteSwap64Word64
w )Int -> ST s ()
loop (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)goWord8Chunk ::Int->Int->STs IntgoWord8Chunk :: Int -> Int -> ST s Int
goWord8Chunk !Int
i' !Int
cl =Int -> ST s Int
loop Int
i' whereloop ::Int->STs Intloop :: Int -> ST s Int
loop !Int
i |Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
cl =Int -> ST s Int
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
returnInt
i |Bool
otherwise=doletw :: Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba Int
i MutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i )Word8
w Int -> ST s Int
loop (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
#else
increatel(\mba->gobamba0l)wherego::ByteArray->MutableByteArrays->Int->Int->STs()go!ba!mba!i!l|i>=l=return()|otherwise=doletw=indexWord8ArraybaiwriteWord8Arraymba(l-1-i)wgobamba(i+1)l
#endif
-- | /O(n)/ The 'intercalate' function takes a 'ShortByteString' and a list of-- 'ShortByteString's and concatenates the list after interspersing the first-- argument between each element of the list.---- @since 0.11.3.0intercalate ::ShortByteString ->[ShortByteString ]->ShortByteString intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString
intercalate ShortByteString
sep =\case[]->ShortByteString
empty [ShortByteString
x ]->ShortByteString
x -- This branch exists for laziness, not speed(ShortByteString
sbs :[ShortByteString]
t )->let!totalLen :: Int
totalLen =(Int -> ShortByteString -> Int) -> Int -> [ShortByteString] -> Int
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl'(\Int
acc ShortByteString
chunk ->Int
acc Int -> Int -> Int
+! ShortByteString -> Int
length ShortByteString
sep Int -> Int -> Int
+! ShortByteString -> Int
length ShortByteString
chunk )(ShortByteString -> Int
length ShortByteString
sbs )[ShortByteString]
t inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
totalLen (\MutableByteArray s
mba ->let!l :: Int
l =ShortByteString -> Int
length ShortByteString
sbs inByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
l ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
forall s. MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
go MutableByteArray s
mba Int
l [ShortByteString]
t )whereba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sep lba :: Int
lba =ShortByteString -> Int
length ShortByteString
sep go ::MutableByteArrays ->Int->[ShortByteString ]->STs ()go :: forall s. MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
go MutableByteArray s
_Int
_[]=() -> ST s ()
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure()go MutableByteArray s
mba !Int
off (ShortByteString
chunk :[ShortByteString]
chunks )=doletlc :: Int
lc =ShortByteString -> Int
length ShortByteString
chunk ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray ByteArray
ba Int
0MutableByteArray s
mba Int
off Int
lba ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
chunk )Int
0MutableByteArray s
mba (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lba )Int
lc MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
forall s. MutableByteArray s -> Int -> [ShortByteString] -> ST s ()
go MutableByteArray s
mba (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lc Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lba )[ShortByteString]
chunks +! :: Int -> Int -> Int
(+!) =String -> Int -> Int -> Int
checkedAdd String
"Short.intercalate"-- ----------------------------------------------------------------------- Reducing 'ShortByteString's-- | 'foldl', applied to a binary operator, a starting value (typically-- the left-identity of the operator), and a ShortByteString, reduces the-- ShortByteString using the binary operator, from left to right.---- @since 0.11.3.0foldl ::(a ->Word8->a )->a ->ShortByteString ->a foldl :: forall a. (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl a -> Word8 -> a
f a
v =(a -> Word8 -> a) -> a -> [Word8] -> a
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldla -> Word8 -> a
f a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> [Word8]
unpack -- | 'foldl'' is like 'foldl', but strict in the accumulator.---- @since 0.11.3.0foldl' ::(a ->Word8->a )->a ->ShortByteString ->a foldl' :: forall a. (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' a -> Word8 -> a
f a
v =(a -> Word8 -> a) -> a -> [Word8] -> a
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl'a -> Word8 -> a
f a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> [Word8]
unpack -- | 'foldr', applied to a binary operator, a starting value-- (typically the right-identity of the operator), and a ShortByteString,-- reduces the ShortByteString using the binary operator, from right to left.---- @since 0.11.3.0foldr ::(Word8->a ->a )->a ->ShortByteString ->a foldr :: forall a. (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr Word8 -> a -> a
k a
v =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs w :: Int -> Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba go :: Int -> a
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =a
v |Bool
otherwise=Word8 -> a -> a
k (Int -> Word8
w Int
n )(Int -> a
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))inInt -> a
go Int
0{-# INLINEfoldr #-}-- | 'foldr'' is like 'foldr', but strict in the accumulator.---- @since 0.11.3.0foldr' ::(Word8->a ->a )->a ->ShortByteString ->a foldr' :: forall a. (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' Word8 -> a -> a
k a
v =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs w :: Int -> Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba go :: Int -> a -> a
go !Int
ix !a
v' |Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
0=a
v' |Bool
otherwise=Int -> a -> a
go (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(Word8 -> a -> a
k (Int -> Word8
w Int
ix )a
v' )inInt -> a -> a
go (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)a
v {-# INLINEfoldr' #-}-- | 'foldl1' is a variant of 'foldl' that has no starting value-- argument, and thus must be applied to non-empty 'ShortByteString's.-- An exception will be thrown in the case of an empty ShortByteString.---- @since 0.11.3.0foldl1 ::HasCallStack=>(Word8->Word8->Word8)->ShortByteString ->Word8foldl1 :: HasCallStack =>
(Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1 Word8 -> Word8 -> Word8
k =(Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldl1Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> [Word8]
unpack -- | 'foldl1'' is like 'foldl1', but strict in the accumulator.-- An exception will be thrown in the case of an empty ShortByteString.---- @since 0.11.3.0foldl1' ::HasCallStack=>(Word8->Word8->Word8)->ShortByteString ->Word8foldl1' :: HasCallStack =>
(Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1' Word8 -> Word8 -> Word8
k =(Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall a. HasCallStack => (a -> a -> a) -> [a] -> a
List.foldl1'Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> [Word8]
unpack -- | 'foldr1' is a variant of 'foldr' that has no starting value argument,-- and thus must be applied to non-empty 'ShortByteString's-- An exception will be thrown in the case of an empty ShortByteString.---- @since 0.11.3.0foldr1 ::HasCallStack=>(Word8->Word8->Word8)->ShortByteString ->Word8foldr1 :: HasCallStack =>
(Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1 Word8 -> Word8 -> Word8
k =(Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldr1Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> [Word8]
unpack -- | 'foldr1'' is a variant of 'foldr1', but is strict in the-- accumulator.---- @since 0.11.3.0foldr1' ::HasCallStack=>(Word8->Word8->Word8)->ShortByteString ->Word8foldr1' :: HasCallStack =>
(Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1' Word8 -> Word8 -> Word8
k =\ShortByteString
sbs ->ifShortByteString -> Bool
null ShortByteString
sbs thenString -> Word8
forall a. HasCallStack => String -> a
errorEmptySBS String
"foldr1'"else(Word8 -> Word8 -> Word8) -> Word8 -> ShortByteString -> Word8
forall a. (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' Word8 -> Word8 -> Word8
k (HasCallStack => ShortByteString -> Word8
ShortByteString -> Word8
last ShortByteString
sbs )(HasCallStack => ShortByteString -> ShortByteString
ShortByteString -> ShortByteString
init ShortByteString
sbs )-- ----------------------------------------------------------------------- Special folds-- | /O(n)/ Applied to a predicate and a 'ShortByteString', 'all' determines-- if all elements of the 'ShortByteString' satisfy the predicate.---- @since 0.11.3.0all ::(Word8->Bool)->ShortByteString ->Boolall :: (Word8 -> Bool) -> ShortByteString -> Bool
all Word8 -> Bool
k =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs w :: Int -> Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba go :: Int -> Bool
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =Bool
True|Bool
otherwise=Word8 -> Bool
k (Int -> Word8
w Int
n )Bool -> Bool -> Bool
&&Int -> Bool
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)inInt -> Bool
go Int
0-- | /O(n)/ Applied to a predicate and a 'ShortByteString', 'any' determines if-- any element of the 'ShortByteString' satisfies the predicate.---- @since 0.11.3.0any ::(Word8->Bool)->ShortByteString ->Boolany :: (Word8 -> Bool) -> ShortByteString -> Bool
any Word8 -> Bool
k =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs w :: Int -> Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba go :: Int -> Bool
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =Bool
False|Bool
otherwise=Word8 -> Bool
k (Int -> Word8
w Int
n )Bool -> Bool -> Bool
||Int -> Bool
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)inInt -> Bool
go Int
0-- ----------------------------------------------------------------------- Substrings-- | /O(n)/ 'take' @n@, applied to a ShortByteString @xs@, returns the prefix-- of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@.---- Note: copies the entire byte array---- @since 0.11.3.0take ::Int->ShortByteString ->ShortByteString take :: Int -> ShortByteString -> ShortByteString
take =\Int
n ->\ShortByteString
sbs ->letsl :: Int
sl =ShortByteString -> Int
length ShortByteString
sbs inif|Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
sl ->ShortByteString
sbs |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->ShortByteString
empty |Bool
otherwise->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
n ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
n -- | Similar to 'Prelude.takeWhile',-- returns the longest (possibly empty) prefix of elements-- satisfying the predicate.---- @since 0.11.3.0takeWhile ::(Word8->Bool)->ShortByteString ->ShortByteString takeWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
takeWhile Word8 -> Bool
f =\ShortByteString
sbs ->Int -> ShortByteString -> ShortByteString
take ((Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
f )ShortByteString
sbs )ShortByteString
sbs -- | /O(n)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@.-- Takes @n@ elements from end of bytestring.---- >>> takeEnd 3 "abcdefg"-- "efg"-- >>> takeEnd 0 "abcdefg"-- ""-- >>> takeEnd 4 "abc"-- "abc"---- @since 0.11.3.0takeEnd ::Int->ShortByteString ->ShortByteString takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd Int
n =\ShortByteString
sbs ->letsl :: Int
sl =ShortByteString -> Int
length ShortByteString
sbs inif|Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
sl ->ShortByteString
sbs |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->ShortByteString
empty |Bool
otherwise->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
n ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )(Int -> Int -> Int
forall a. Ord a => a -> a -> a
maxInt
0(Int
sl Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n ))MutableByteArray s
mba Int
0Int
n -- | Returns the longest (possibly empty) suffix of elements-- satisfying the predicate.---- @'takeWhileEnd' p@ is equivalent to @'reverse' . 'takeWhile' p . 'reverse'@.---- @since 0.11.3.0takeWhileEnd ::(Word8->Bool)->ShortByteString ->ShortByteString takeWhileEnd :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
takeWhileEnd Word8 -> Bool
f =\ShortByteString
sbs ->Int -> ShortByteString -> ShortByteString
drop ((Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
f )ShortByteString
sbs )ShortByteString
sbs -- | /O(n)/ 'drop' @n@ @xs@ returns the suffix of @xs@ after the first n elements, or 'empty' if @n > 'length' xs@.---- Note: copies the entire byte array---- @since 0.11.3.0drop ::Int->ShortByteString ->ShortByteString drop :: Int -> ShortByteString -> ShortByteString
drop =\Int
n ->\ShortByteString
sbs ->letlen :: Int
len =ShortByteString -> Int
length ShortByteString
sbs inif|Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->ShortByteString
sbs |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
len ->ShortByteString
empty |Bool
otherwise->letnewLen :: Int
newLen =Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n inInt -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
newLen ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
n MutableByteArray s
mba Int
0Int
newLen -- | /O(n)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@.-- Drops @n@ elements from end of bytestring.---- >>> dropEnd 3 "abcdefg"-- "abcd"-- >>> dropEnd 0 "abcdefg"-- "abcdefg"-- >>> dropEnd 4 "abc"-- ""---- @since 0.11.3.0dropEnd ::Int->ShortByteString ->ShortByteString dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd Int
n =\ShortByteString
sbs ->letsl :: Int
sl =ShortByteString -> Int
length ShortByteString
sbs nl :: Int
nl =Int
sl Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n inif|Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
sl ->ShortByteString
empty |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->ShortByteString
sbs |Bool
otherwise->Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
nl -- | Similar to 'Prelude.dropWhile',-- drops the longest (possibly empty) prefix of elements-- satisfying the predicate and returns the remainder.---- Note: copies the entire byte array---- @since 0.11.3.0dropWhile ::(Word8->Bool)->ShortByteString ->ShortByteString dropWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhile Word8 -> Bool
f =\ShortByteString
sbs ->Int -> ShortByteString -> ShortByteString
drop ((Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
f )ShortByteString
sbs )ShortByteString
sbs -- | Similar to 'Prelude.dropWhileEnd',-- drops the longest (possibly empty) suffix of elements-- satisfying the predicate and returns the remainder.---- @'dropWhileEnd' p@ is equivalent to @'reverse' . 'dropWhile' p . 'reverse'@.---- @since 0.11.3.0dropWhileEnd ::(Word8->Bool)->ShortByteString ->ShortByteString dropWhileEnd :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhileEnd Word8 -> Bool
f =\ShortByteString
sbs ->Int -> ShortByteString -> ShortByteString
take ((Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
f )ShortByteString
sbs )ShortByteString
sbs -- | Returns the longest (possibly empty) suffix of elements which __do not__-- satisfy the predicate and the remainder of the string.---- 'breakEnd' @p@ is equivalent to @'spanEnd' (not . p)@ and to @('takeWhileEnd' (not . p) &&& 'dropWhileEnd' (not . p))@.---- @since 0.11.3.0breakEnd ::(Word8->Bool)->ShortByteString ->(ShortByteString ,ShortByteString )breakEnd :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
breakEnd Word8 -> Bool
p =\ShortByteString
sbs ->Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt ((Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil Word8 -> Bool
p ShortByteString
sbs )ShortByteString
sbs -- | Similar to 'Prelude.break',-- returns the longest (possibly empty) prefix of elements which __do not__-- satisfy the predicate and the remainder of the string.---- 'break' @p@ is equivalent to @'span' (not . p)@ and to @('takeWhile' (not . p) &&& 'dropWhile' (not . p))@.---- @since 0.11.3.0break ::(Word8->Bool)->ShortByteString ->(ShortByteString ,ShortByteString )break :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break Word8 -> Bool
p =\ShortByteString
sbs ->case(Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength Word8 -> Bool
p ShortByteString
sbs ofInt
n ->(Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
sbs ,Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
sbs ){-# INLINEbreak #-}-- | Similar to 'Prelude.span',-- returns the longest (possibly empty) prefix of elements-- satisfying the predicate and the remainder of the string.---- 'span' @p@ is equivalent to @'break' (not . p)@ and to @('takeWhile' p &&& 'dropWhile' p)@.---- @since 0.11.3.0span ::(Word8->Bool)->ShortByteString ->(ShortByteString ,ShortByteString )span :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
span Word8 -> Bool
p =(Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
p )-- | Returns the longest (possibly empty) suffix of elements-- satisfying the predicate and the remainder of the string.---- 'spanEnd' @p@ is equivalent to @'breakEnd' (not . p)@ and to @('takeWhileEnd' p &&& 'dropWhileEnd' p)@.---- We have---- > spanEnd (not . isSpace) "x y z" == ("x y ", "z")---- and---- > spanEnd (not . isSpace) sbs-- > ==-- > let (x, y) = span (not . isSpace) (reverse sbs) in (reverse y, reverse x)---- @since 0.11.3.0spanEnd ::(Word8->Bool)->ShortByteString ->(ShortByteString ,ShortByteString )spanEnd :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
spanEnd Word8 -> Bool
p =\ShortByteString
sbs ->Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt ((Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
p )ShortByteString
sbs )ShortByteString
sbs -- | /O(n)/ 'splitAt' @n sbs@ is equivalent to @('take' n sbs, 'drop' n sbs)@.---- Note: copies the substrings---- @since 0.11.3.0splitAt ::Int->ShortByteString ->(ShortByteString ,ShortByteString )splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt Int
n =\ShortByteString
sbs ->if|Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->(ShortByteString
empty ,ShortByteString
sbs )|Bool
otherwise->letslen :: Int
slen =ShortByteString -> Int
length ShortByteString
sbs inif|Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
slen ->(ShortByteString
sbs ,ShortByteString
empty )|Bool
otherwise->letrlen :: Int
rlen =Int
slen Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n lsbs :: ShortByteString
lsbs =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
n ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
0MutableByteArray s
mba Int
0Int
n rsbs :: ShortByteString
rsbs =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
rlen ((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
n MutableByteArray s
mba Int
0Int
rlen in(ShortByteString
lsbs ,ShortByteString
rsbs )-- | /O(n)/ Break a 'ShortByteString' into pieces separated by the byte-- argument, consuming the delimiter. I.e.---- > split 10 "a\nb\nd\ne" == ["a","b","d","e"] -- fromEnum '\n' == 10-- > split 97 "aXaXaXa" == ["","X","X","X",""] -- fromEnum 'a' == 97-- > split 120 "x" == ["",""] -- fromEnum 'x' == 120-- > split undefined "" == [] -- and not [""]---- and---- > intercalate [c] . split c == id-- > split == splitWith . (==)---- Note: copies the substrings---- @since 0.11.3.0split ::Word8->ShortByteString ->[ShortByteString ]split :: Word8 -> ShortByteString -> [ShortByteString]
split Word8
w =(Word8 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
w )-- | /O(n)/ Splits a 'ShortByteString' into components delimited by-- separators, where the predicate returns True for a separator element.-- The resulting components do not contain the separators. Two adjacent-- separators result in an empty component in the output. eg.---- > splitWith (==97) "aabbaca" == ["","","bb","c",""] -- fromEnum 'a' == 97-- > splitWith undefined "" == [] -- and not [""]---- @since 0.11.3.0splitWith ::(Word8->Bool)->ShortByteString ->[ShortByteString ]splitWith :: (Word8 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith Word8 -> Bool
p =\ShortByteString
sbs ->if|ShortByteString -> Bool
null ShortByteString
sbs ->[]|Bool
otherwise->ShortByteString -> [ShortByteString]
go ShortByteString
sbs wherego :: ShortByteString -> [ShortByteString]
go ShortByteString
sbs' |ShortByteString -> Bool
null ShortByteString
sbs' =[ShortByteString
empty ]|Bool
otherwise=case(Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break Word8 -> Bool
p ShortByteString
sbs' of(ShortByteString
a ,ShortByteString
b )|ShortByteString -> Bool
null ShortByteString
b ->[ShortByteString
a ]|Bool
otherwise->ShortByteString
a ShortByteString -> [ShortByteString] -> [ShortByteString]
forall a. a -> [a] -> [a]
:ShortByteString -> [ShortByteString]
go (HasCallStack => ShortByteString -> ShortByteString
ShortByteString -> ShortByteString
tail ShortByteString
b )-- | /O(n)/ The 'stripSuffix' function takes two ShortByteStrings and returns 'Just'-- the remainder of the second iff the first is its suffix, and otherwise-- 'Nothing'.---- @since 0.11.3.0stripSuffix ::ShortByteString ->ShortByteString ->MaybeShortByteString stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripSuffix ShortByteString
sbs1 =\ShortByteString
sbs2 ->doletl1 :: Int
l1 =ShortByteString -> Int
length ShortByteString
sbs1 l2 :: Int
l2 =ShortByteString -> Int
length ShortByteString
sbs2 if|ShortByteString -> ShortByteString -> Bool
isSuffixOf ShortByteString
sbs1 ShortByteString
sbs2 ->ifShortByteString -> Bool
null ShortByteString
sbs1 thenShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
JustShortByteString
sbs2 elseShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just(ShortByteString -> Maybe ShortByteString)
-> ShortByteString -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$!Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l1 )((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
dst ->doByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs2 )Int
0MutableByteArray s
dst Int
0(Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l1 )|Bool
otherwise->Maybe ShortByteString
forall a. Maybe a
Nothing-- | /O(n)/ The 'stripPrefix' function takes two ShortByteStrings and returns 'Just'-- the remainder of the second iff the first is its prefix, and otherwise-- 'Nothing'.---- @since 0.11.3.0stripPrefix ::ShortByteString ->ShortByteString ->MaybeShortByteString stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripPrefix ShortByteString
sbs1 =\ShortByteString
sbs2 ->doletl1 :: Int
l1 =ShortByteString -> Int
length ShortByteString
sbs1 l2 :: Int
l2 =ShortByteString -> Int
length ShortByteString
sbs2 if|ShortByteString -> ShortByteString -> Bool
isPrefixOf ShortByteString
sbs1 ShortByteString
sbs2 ->ifShortByteString -> Bool
null ShortByteString
sbs1 thenShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
JustShortByteString
sbs2 elseShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just(ShortByteString -> Maybe ShortByteString)
-> ShortByteString -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$!Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l1 )((forall s. MutableByteArray s -> ST s ()) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
dst ->doByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> ByteArray
asBA ShortByteString
sbs2 )Int
l1 MutableByteArray s
dst Int
0(Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l1 )|Bool
otherwise->Maybe ShortByteString
forall a. Maybe a
Nothing-- ----------------------------------------------------------------------- Unfolds and replicates-- | /O(n)/ 'replicate' @n x@ is a ShortByteString of length @n@ with @x@-- the value of every element. The following holds:---- > replicate w c = unfoldr w (\u -> Just (u,u)) c---- @since 0.11.3.0replicate ::Int->Word8->ShortByteString replicate :: Int -> Word8 -> ShortByteString
replicate Int
w Word8
c |Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0=ShortByteString
empty |Bool
otherwise=Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
w (\MutableByteArray s
mba ->MutableByteArray s -> Int -> Int -> Int -> ST s ()
forall s. MutableByteArray s -> Int -> Int -> Int -> ST s ()
setByteArray MutableByteArray s
mba Int
0Int
w (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralWord8
c ))-- | /O(n)/, where /n/ is the length of the result. The 'unfoldr'-- function is analogous to the List \'unfoldr\'. 'unfoldr' builds a-- ShortByteString from a seed value. The function takes the element and-- returns 'Nothing' if it is done producing the ShortByteString or returns-- 'Just' @(a,b)@, in which case, @a@ is the next byte in the string,-- and @b@ is the seed value for further production.---- This function is not efficient/safe. It will build a list of @[Word8]@-- and run the generator until it returns `Nothing`, otherwise recurse infinitely,-- then finally create a 'ShortByteString'.---- If you know the maximum length, consider using 'unfoldrN'.---- Examples:---- > unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0-- > == pack [0, 1, 2, 3, 4, 5]---- @since 0.11.3.0unfoldr ::(a ->Maybe(Word8,a ))->a ->ShortByteString unfoldr :: forall a. (a -> Maybe (Word8, a)) -> a -> ShortByteString
unfoldr a -> Maybe (Word8, a)
f =\a
x0 ->[Word8] -> ShortByteString
packBytesRev ([Word8] -> ShortByteString) -> [Word8] -> ShortByteString
forall a b. (a -> b) -> a -> b
$a -> [Word8] -> [Word8]
go a
x0 []wherego :: a -> [Word8] -> [Word8]
go a
x [Word8]
words' =casea -> Maybe (Word8, a)
f a
x ofMaybe (Word8, a)
Nothing->[Word8]
words' Just(Word8
w ,a
x' )->a -> [Word8] -> [Word8]
go a
x' (Word8
w Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
words' )-- | /O(n)/ Like 'unfoldr', 'unfoldrN' builds a ShortByteString from a seed-- value. However, the length of the result is limited by the first-- argument to 'unfoldrN'. This function is more efficient than 'unfoldr'-- when the maximum length of the result is known.---- The following equation relates 'unfoldrN' and 'unfoldr':---- > fst (unfoldrN n f s) == take n (unfoldr f s)---- @since 0.11.3.0unfoldrN ::foralla .Int->(a ->Maybe(Word8,a ))->a ->(ShortByteString ,Maybea )unfoldrN :: forall a.
Int -> (a -> Maybe (Word8, a)) -> a -> (ShortByteString, Maybe a)
unfoldrN Int
i a -> Maybe (Word8, a)
f =\a
x0 ->if|Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
0->(ShortByteString
empty ,a -> Maybe a
forall a. a -> Maybe a
Justa
x0 )|Bool
otherwise->Int
-> (forall {s}. MutableByteArray s -> ST s (Int, Maybe a))
-> (ShortByteString, Maybe a)
forall a.
Int
-> (forall s. MutableByteArray s -> ST s (Int, a))
-> (ShortByteString, a)
createAndTrim Int
i ((forall {s}. MutableByteArray s -> ST s (Int, Maybe a))
-> (ShortByteString, Maybe a))
-> (forall {s}. MutableByteArray s -> ST s (Int, Maybe a))
-> (ShortByteString, Maybe a)
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->MutableByteArray s -> a -> Int -> ST s (Int, Maybe a)
forall s. MutableByteArray s -> a -> Int -> ST s (Int, Maybe a)
go MutableByteArray s
mba a
x0 Int
0wherego ::foralls .MutableByteArrays ->a ->Int->STs (Int,Maybea )go :: forall s. MutableByteArray s -> a -> Int -> ST s (Int, Maybe a)
go !MutableByteArray s
mba !a
x !Int
n =a -> Int -> ST s (Int, Maybe a)
go' a
x Int
n wherego' ::a ->Int->STs (Int,Maybea )go' :: a -> Int -> ST s (Int, Maybe a)
go' !a
x' !Int
n' |Int
n' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
i =(Int, Maybe a) -> ST s (Int, Maybe a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return(Int
n' ,a -> Maybe a
forall a. a -> Maybe a
Justa
x' )|Bool
otherwise=casea -> Maybe (Word8, a)
f a
x' ofMaybe (Word8, a)
Nothing->(Int, Maybe a) -> ST s (Int, Maybe a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return(Int
n' ,Maybe a
forall a. Maybe a
Nothing)Just(Word8
w ,a
x'' )->doMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
n' Word8
w a -> Int -> ST s (Int, Maybe a)
go' a
x'' (Int
n' Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1){-# INLINEunfoldrN #-}-- ---------------------------------------------------------------------- Predicates-- | Check whether one string is a substring of another.---- @since 0.11.3.0isInfixOf ::ShortByteString ->ShortByteString ->BoolisInfixOf :: ShortByteString -> ShortByteString -> Bool
isInfixOf ShortByteString
sbs =\ShortByteString
s ->ShortByteString -> Bool
null ShortByteString
sbs Bool -> Bool -> Bool
||Bool -> Bool
not(ShortByteString -> Bool
null (ShortByteString -> Bool) -> ShortByteString -> Bool
forall a b. (a -> b) -> a -> b
$(ShortByteString, ShortByteString) -> ShortByteString
forall a b. (a, b) -> b
snd((ShortByteString, ShortByteString) -> ShortByteString)
-> (ShortByteString, ShortByteString) -> ShortByteString
forall a b. (a -> b) -> a -> b
$((ShortByteString
-> ShortByteString -> (ShortByteString, ShortByteString))
-> ShortByteString
-> ShortByteString
-> (ShortByteString, ShortByteString)
forall a. a -> a
GHC.Exts.inlineShortByteString
-> ShortByteString -> (ShortByteString, ShortByteString)
breakSubstring )ShortByteString
sbs ShortByteString
s )-- |/O(n)/ The 'isPrefixOf' function takes two ShortByteStrings and returns 'True'-- iff the first is a prefix of the second.---- @since 0.11.3.0isPrefixOf ::ShortByteString ->ShortByteString ->BoolisPrefixOf :: ShortByteString -> ShortByteString -> Bool
isPrefixOf ShortByteString
sbs1 =\ShortByteString
sbs2 ->doletl1 :: Int
l1 =ShortByteString -> Int
length ShortByteString
sbs1 l2 :: Int
l2 =ShortByteString -> Int
length ShortByteString
sbs2 if|Int
l1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0->Bool
True|Int
l2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
l1 ->Bool
False|Bool
otherwise->leti :: Int
i =ByteArray -> Int -> ByteArray -> Int -> Int -> Int
compareByteArraysOff (ShortByteString -> ByteArray
asBA ShortByteString
sbs1 )Int
0(ShortByteString -> ByteArray
asBA ShortByteString
sbs2 )Int
0Int
l1 inInt
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0-- | /O(n)/ The 'isSuffixOf' function takes two ShortByteStrings and returns 'True'-- iff the first is a suffix of the second.---- The following holds:---- > isSuffixOf x y == reverse x `isPrefixOf` reverse y---- @since 0.11.3.0isSuffixOf ::ShortByteString ->ShortByteString ->BoolisSuffixOf :: ShortByteString -> ShortByteString -> Bool
isSuffixOf ShortByteString
sbs1 =\ShortByteString
sbs2 ->doletl1 :: Int
l1 =ShortByteString -> Int
length ShortByteString
sbs1 l2 :: Int
l2 =ShortByteString -> Int
length ShortByteString
sbs2 if|Int
l1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0->Bool
True|Int
l2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
l1 ->Bool
False|Bool
otherwise->leti :: Int
i =ByteArray -> Int -> ByteArray -> Int -> Int -> Int
compareByteArraysOff (ShortByteString -> ByteArray
asBA ShortByteString
sbs1 )Int
0(ShortByteString -> ByteArray
asBA ShortByteString
sbs2 )(Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l1 )Int
l1 inInt
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0-- | Break a string on a substring, returning a pair of the part of the-- string prior to the match, and the rest of the string.---- The following relationships hold:---- > break (== c) l == breakSubstring (singleton c) l---- For example, to tokenise a string, dropping delimiters:---- > tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)-- > where (h,t) = breakSubstring x y---- To skip to the first occurrence of a string:---- > snd (breakSubstring x y)---- To take the parts of a string before a delimiter:---- > fst (breakSubstring x y)---- Note that calling `breakSubstring x` does some preprocessing work, so-- you should avoid unnecessarily duplicating breakSubstring calls with the same-- pattern.---- @since 0.11.3.0breakSubstring ::ShortByteString -- ^ String to search for->ShortByteString -- ^ String to search in->(ShortByteString ,ShortByteString )-- ^ Head and tail of string broken at substringbreakSubstring :: ShortByteString
-> ShortByteString -> (ShortByteString, ShortByteString)
breakSubstring ShortByteString
pat =caseInt
lp ofInt
0->(ShortByteString
empty ,)Int
1->Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte (HasCallStack => ShortByteString -> Word8
ShortByteString -> Word8
head ShortByteString
pat )Int
_->ifInt
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
8Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Word -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize(Word
0::Word)thenShortByteString -> (ShortByteString, ShortByteString)
shift elseShortByteString -> (ShortByteString, ShortByteString)
karpRabin wherelp :: Int
lp =ShortByteString -> Int
length ShortByteString
pat karpRabin ::ShortByteString ->(ShortByteString ,ShortByteString )karpRabin :: ShortByteString -> (ShortByteString, ShortByteString)
karpRabin ShortByteString
src |ShortByteString -> Int
length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
lp =(ShortByteString
src ,ShortByteString
empty )|Bool
otherwise=Word32 -> Int -> (ShortByteString, ShortByteString)
search (ShortByteString -> Word32
rollingHash (ShortByteString -> Word32) -> ShortByteString -> Word32
forall a b. (a -> b) -> a -> b
$Int -> ShortByteString -> ShortByteString
take Int
lp ShortByteString
src )Int
lp wherek :: Word32
k =Word32
2891336453::Word32rollingHash :: ShortByteString -> Word32
rollingHash =(Word32 -> Word8 -> Word32) -> Word32 -> ShortByteString -> Word32
forall a. (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' (\Word32
h Word8
b ->Word32
h Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
*Word32
k Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegralWord8
b )Word32
0hp :: Word32
hp =ShortByteString -> Word32
rollingHash ShortByteString
pat m :: Word32
m =Word32
k Word32 -> Int -> Word32
forall a b. (Num a, Integral b) => a -> b -> a
^Int
lp get :: Int -> Word32
get =Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Word8 -> Word32) -> (Int -> Word8) -> Int -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> Int -> Word8
unsafeIndex ShortByteString
src search :: Word32 -> Int -> (ShortByteString, ShortByteString)
search !Word32
hs !Int
i |Word32
hp Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
==Word32
hs Bool -> Bool -> Bool
&&ShortByteString
pat ShortByteString -> ShortByteString -> Bool
forall a. Eq a => a -> a -> Bool
==Int -> ShortByteString -> ShortByteString
take Int
lp ShortByteString
b =(ShortByteString, ShortByteString)
u |ShortByteString -> Int
length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
i =(ShortByteString
src ,ShortByteString
empty )-- not found|Bool
otherwise=Word32 -> Int -> (ShortByteString, ShortByteString)
search Word32
hs' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)whereu :: (ShortByteString, ShortByteString)
u @(ShortByteString
_,ShortByteString
b )=Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
lp )ShortByteString
src hs' :: Word32
hs' =Word32
hs Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
*Word32
k Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+Int -> Word32
get Int
i Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
-Word32
m Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
*Int -> Word32
get (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
lp ){-# INLINEkarpRabin #-}shift ::ShortByteString ->(ShortByteString ,ShortByteString )shift :: ShortByteString -> (ShortByteString, ShortByteString)
shift !ShortByteString
src |ShortByteString -> Int
length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
lp =(ShortByteString
src ,ShortByteString
empty )|Bool
otherwise=Word -> Int -> (ShortByteString, ShortByteString)
search (ShortByteString -> Word
intoWord (ShortByteString -> Word) -> ShortByteString -> Word
forall a b. (a -> b) -> a -> b
$Int -> ShortByteString -> ShortByteString
take Int
lp ShortByteString
src )Int
lp whereintoWord ::ShortByteString ->WordintoWord :: ShortByteString -> Word
intoWord =(Word -> Word8 -> Word) -> Word -> ShortByteString -> Word
forall a. (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' (\Word
w Word8
b ->(Word
w Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL`Int
8)Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|.Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegralWord8
b )Word
0wp :: Word
wp =ShortByteString -> Word
intoWord ShortByteString
pat mask' :: Word
mask' =(Word
1Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL`(Int
8Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
lp ))Word -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1search :: Word -> Int -> (ShortByteString, ShortByteString)
search !Word
w !Int
i |Word
w Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
==Word
wp =Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
lp )ShortByteString
src |ShortByteString -> Int
length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
i =(ShortByteString
src ,ShortByteString
empty )|Bool
otherwise=Word -> Int -> (ShortByteString, ShortByteString)
search Word
w' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)whereb :: Word
b =Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral(ShortByteString -> Int -> Word8
unsafeIndex ShortByteString
src Int
i )w' :: Word
w' =Word
mask' Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&.((Word
w Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL`Int
8)Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|.Word
b ){-# INLINEshift #-}-- ---------------------------------------------------------------------- Searching ShortByteString-- | /O(n)/ 'elem' is the 'ShortByteString' membership predicate.---- @since 0.11.3.0elem ::Word8->ShortByteString ->Boolelem :: Word8 -> ShortByteString -> Bool
elem Word8
c =\ShortByteString
sbs ->caseWord8 -> ShortByteString -> Maybe Int
elemIndex Word8
c ShortByteString
sbs ofMaybe Int
Nothing->Bool
False;Maybe Int
_->Bool
True-- | /O(n)/ 'filter', applied to a predicate and a ShortByteString,-- returns a ShortByteString containing those characters that satisfy the-- predicate.---- @since 0.11.3.0filter ::(Word8->Bool)->ShortByteString ->ShortByteString filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
filter Word8 -> Bool
k =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs inif|Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->ShortByteString
sbs |Bool
otherwise->Int
-> (forall s. MutableByteArray s -> ST s Int) -> ShortByteString
createAndTrim' Int
l ((forall s. MutableByteArray s -> ST s Int) -> ShortByteString)
-> (forall s. MutableByteArray s -> ST s Int) -> ShortByteString
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba ->MutableByteArray s -> ByteArray -> Int -> ST s Int
forall s. MutableByteArray s -> ByteArray -> Int -> ST s Int
go MutableByteArray s
mba (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
l wherego ::foralls .MutableByteArrays -- mutable output bytestring->ByteArray-- input bytestring->Int-- length of input bytestring->STs Intgo :: forall s. MutableByteArray s -> ByteArray -> Int -> ST s Int
go !MutableByteArray s
mba ByteArray
ba !Int
l =Int -> Int -> ST s Int
go' Int
0Int
0wherego' ::Int-- bytes read->Int-- bytes written->STs Intgo' :: Int -> Int -> ST s Int
go' !Int
br !Int
bw |Int
br Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =Int -> ST s Int
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
returnInt
bw |Bool
otherwise=doletw :: Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba Int
br ifWord8 -> Bool
k Word8
w thendoMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba Int
bw Word8
w Int -> Int -> ST s Int
go' (Int
br Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)(Int
bw Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)elseInt -> Int -> ST s Int
go' (Int
br Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)Int
bw {-# INLINEfilter #-}-- | /O(n)/ The 'find' function takes a predicate and a ShortByteString,-- and returns the first element in matching the predicate, or 'Nothing'-- if there is no such element.---- > find f p = case findIndex f p of Just n -> Just (p ! n) ; _ -> Nothing---- @since 0.11.3.0find ::(Word8->Bool)->ShortByteString ->MaybeWord8find :: (Word8 -> Bool) -> ShortByteString -> Maybe Word8
find Word8 -> Bool
f =\ShortByteString
sbs ->case(Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word8 -> Bool
f ShortByteString
sbs ofJustInt
n ->Word8 -> Maybe Word8
forall a. a -> Maybe a
Just(ShortByteString
sbs HasCallStack => ShortByteString -> Int -> Word8
ShortByteString -> Int -> Word8
`index` Int
n )Maybe Int
_->Maybe Word8
forall a. Maybe a
Nothing{-# INLINEfind #-}-- | /O(n)/ The 'partition' function takes a predicate a ShortByteString and returns-- the pair of ShortByteStrings with elements which do and do not satisfy the-- predicate, respectively; i.e.,---- > partition p bs == (filter p sbs, filter (not . p) sbs)---- @since 0.11.3.0partition ::(Word8->Bool)->ShortByteString ->(ShortByteString ,ShortByteString )partition :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
partition Word8 -> Bool
k =\ShortByteString
sbs ->letlen :: Int
len =ShortByteString -> Int
length ShortByteString
sbs inif|Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0->(ShortByteString
sbs ,ShortByteString
sbs )|Bool
otherwise->Int
-> Int
-> (forall s.
MutableByteArray s -> MutableByteArray s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
createAndTrim2 Int
len Int
len ((forall s.
MutableByteArray s -> MutableByteArray s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString))
-> (forall s.
MutableByteArray s -> MutableByteArray s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
forall a b. (a -> b) -> a -> b
$\MutableByteArray s
mba1 MutableByteArray s
mba2 ->MutableByteArray s
-> MutableByteArray s -> ByteArray -> Int -> ST s (Int, Int)
forall s.
MutableByteArray s
-> MutableByteArray s -> ByteArray -> Int -> ST s (Int, Int)
go MutableByteArray s
mba1 MutableByteArray s
mba2 (ShortByteString -> ByteArray
asBA ShortByteString
sbs )Int
len wherego ::foralls .MutableByteArrays -- mutable output bytestring1->MutableByteArrays -- mutable output bytestring2->ByteArray-- input bytestring->Int-- length of input bytestring->STs (Int,Int)-- (length mba1, length mba2)go :: forall s.
MutableByteArray s
-> MutableByteArray s -> ByteArray -> Int -> ST s (Int, Int)
go !MutableByteArray s
mba1 !MutableByteArray s
mba2 ByteArray
ba !Int
l =Int -> Int -> ST s (Int, Int)
go' Int
0Int
0wherego' ::Int-- bytes read->Int-- bytes written to bytestring 1->STs (Int,Int)-- (length mba1, length mba2)go' :: Int -> Int -> ST s (Int, Int)
go' !Int
br !Int
bw1 |Int
br Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =(Int, Int) -> ST s (Int, Int)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return(Int
bw1 ,Int
br Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
bw1 )|Bool
otherwise=doletw :: Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba Int
br ifWord8 -> Bool
k Word8
w thendoMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba1 Int
bw1 Word8
w Int -> Int -> ST s (Int, Int)
go' (Int
br Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)(Int
bw1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)elsedoMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba2 (Int
br Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
bw1 )Word8
w Int -> Int -> ST s (Int, Int)
go' (Int
br Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)Int
bw1 -- ---------------------------------------------------------------------- Indexing ShortByteString-- | /O(n)/ The 'elemIndex' function returns the index of the first-- element in the given 'ShortByteString' which is equal to the query-- element, or 'Nothing' if there is no such element.---- @since 0.11.3.0elemIndex ::Word8->ShortByteString ->MaybeIntelemIndex :: Word8 -> ShortByteString -> Maybe Int
elemIndex Word8
c =\sbs :: ShortByteString
sbs @(SBS ByteArray#
ba# )->doletl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs IO (Maybe Int) -> Maybe Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO (Maybe Int) -> Maybe Int) -> IO (Maybe Int) -> Maybe Int
forall a b. (a -> b) -> a -> b
$do!CPtrdiff
s <-ByteArray# -> Word8 -> CSize -> IO CPtrdiff
c_elem_index ByteArray#
ba# Word8
c (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
l )Maybe Int -> IO (Maybe Int)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(Maybe Int -> IO (Maybe Int)) -> Maybe Int -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$!ifCPtrdiff
s CPtrdiff -> CPtrdiff -> Bool
forall a. Ord a => a -> a -> Bool
<CPtrdiff
0thenMaybe Int
forall a. Maybe a
NothingelseInt -> Maybe Int
forall a. a -> Maybe a
Just(CPtrdiff -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralCPtrdiff
s )-- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning-- the indices of all elements equal to the query element, in ascending order.---- @since 0.11.3.0elemIndices ::Word8->ShortByteString ->[Int]elemIndices :: Word8 -> ShortByteString -> [Int]
elemIndices Word8
k =(Word8 -> Bool) -> ShortByteString -> [Int]
findIndices (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
k )-- | count returns the number of times its argument appears in the ShortByteString---- @since 0.11.3.0count ::Word8->ShortByteString ->Intcount :: Word8 -> ShortByteString -> Int
count Word8
w =\sbs :: ShortByteString
sbs @(SBS ByteArray#
ba# )->IO Int -> Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral(CSize -> Int) -> IO CSize -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>ByteArray# -> CSize -> Word8 -> IO CSize
BS.c_count_ba ByteArray#
ba# (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ShortByteString -> Int
length ShortByteString
sbs )Word8
w -- | /O(n)/ The 'findIndex' function takes a predicate and a 'ShortByteString' and-- returns the index of the first element in the ShortByteString-- satisfying the predicate.---- @since 0.11.3.0findIndex ::(Word8->Bool)->ShortByteString ->MaybeIntfindIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word8 -> Bool
k =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs w :: Int -> Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba go :: Int -> Maybe Int
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =Maybe Int
forall a. Maybe a
Nothing|Word8 -> Bool
k (Int -> Word8
w Int
n )=Int -> Maybe Int
forall a. a -> Maybe a
JustInt
n |Bool
otherwise=Int -> Maybe Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)inInt -> Maybe Int
go Int
0{-# INLINEfindIndex #-}-- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the-- indices of all elements satisfying the predicate, in ascending order.---- @since 0.11.3.0findIndices ::(Word8->Bool)->ShortByteString ->[Int]findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices Word8 -> Bool
k =\ShortByteString
sbs ->letl :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs w :: Int -> Word8
w =ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba go :: Int -> [Int]
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =[]|Word8 -> Bool
k (Int -> Word8
w Int
n )=Int
n Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:Int -> [Int]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)|Bool
otherwise=Int -> [Int]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)inInt -> [Int]
go Int
0-------------------------------------------------------------------------- Exported low level operationscopyToPtr ::ShortByteString -- ^ source data->Int-- ^ offset into source->Ptra -- ^ destination->Int-- ^ number of bytes to copy->IO()copyToPtr :: forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
copyToPtr ShortByteString
src Int
off Ptr a
dst Int
len =ST RealWorld () -> IO ()
forall a. ST RealWorld a -> IO a
stToIO(ST RealWorld () -> IO ()) -> ST RealWorld () -> IO ()
forall a b. (a -> b) -> a -> b
$ByteArray -> Int -> Ptr a -> Int -> ST RealWorld ()
forall a. ByteArray -> Int -> Ptr a -> Int -> ST RealWorld ()
copyByteArrayToAddr (ShortByteString -> ByteArray
asBA ShortByteString
src )Int
off Ptr a
dst Int
len createFromPtr ::Ptra -- ^ source data->Int-- ^ number of bytes to copy->IOShortByteString createFromPtr :: forall a. Ptr a -> Int -> IO ShortByteString
createFromPtr !Ptr a
ptr Int
len =ST RealWorld ShortByteString -> IO ShortByteString
forall a. ST RealWorld a -> IO a
stToIO(ST RealWorld ShortByteString -> IO ShortByteString)
-> ST RealWorld ShortByteString -> IO ShortByteString
forall a b. (a -> b) -> a -> b
$doMutableByteArray RealWorld
mba <-Int -> ST RealWorld (MutableByteArray RealWorld)
forall s. Int -> ST s (MutableByteArray s)
newByteArray Int
len Ptr a
-> MutableByteArray RealWorld -> Int -> Int -> ST RealWorld ()
forall a.
Ptr a
-> MutableByteArray RealWorld -> Int -> Int -> ST RealWorld ()
copyAddrToByteArray Ptr a
ptr MutableByteArray RealWorld
mba Int
0Int
len ByteArray -> ShortByteString
ShortByteString (ByteArray -> ShortByteString)
-> ST RealWorld ByteArray -> ST RealWorld ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>MutableByteArray RealWorld -> ST RealWorld ByteArray
forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray MutableByteArray RealWorld
mba -------------------------------------------------------------------------- Primop wrappersindexCharArray ::ByteArray->Int->CharindexCharArray :: ByteArray -> Int -> Char
indexCharArray (ByteArrayByteArray#
ba# )(I#Int#
i# )=Char# -> Char
C#(ByteArray# -> Int# -> Char#
indexCharArray#ByteArray#
ba# Int#
i# )indexWord8Array ::ByteArray->Int->Word8indexWord8Array :: ByteArray -> Int -> Word8
indexWord8Array (ByteArrayByteArray#
ba# )(I#Int#
i# )=Word8# -> Word8
W8#(ByteArray# -> Int# -> Word8#
indexWord8Array#ByteArray#
ba# Int#
i# )
#if HS_UNALIGNED_ByteArray_OPS_OK
indexWord8ArrayAsWord64 ::ByteArray->Int->Word64indexWord8ArrayAsWord64 :: ByteArray -> Int -> Word64
indexWord8ArrayAsWord64 (ByteArrayByteArray#
ba# )(I#Int#
i# )=Word64# -> Word64
W64#(ByteArray# -> Int# -> Word64#
indexWord8ArrayAsWord64#ByteArray#
ba# Int#
i# )
#endif
newByteArray ::Int->STs (MutableByteArrays )newByteArray :: forall s. Int -> ST s (MutableByteArray s)
newByteArray len :: Int
len @(I#Int#
len# )=Bool -> ST s (MutableByteArray s) -> ST s (MutableByteArray s)
forall a. HasCallStack => Bool -> a -> a
assert(Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0)(ST s (MutableByteArray s) -> ST s (MutableByteArray s))
-> ST s (MutableByteArray s) -> ST s (MutableByteArray s)
forall a b. (a -> b) -> a -> b
$STRep s (MutableByteArray s) -> ST s (MutableByteArray s)
forall s a. STRep s a -> ST s a
ST(STRep s (MutableByteArray s) -> ST s (MutableByteArray s))
-> STRep s (MutableByteArray s) -> ST s (MutableByteArray s)
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseInt# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray#Int#
len# State# s
s of(#State# s
s' ,MutableByteArray# s
mba# #)->(#State# s
s' ,MutableByteArray# s -> MutableByteArray s
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArrayMutableByteArray# s
mba# #)unsafeFreezeByteArray ::MutableByteArrays ->STs ByteArrayunsafeFreezeByteArray :: forall s. MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray (MutableByteArrayMutableByteArray# s
mba# )=STRep s ByteArray -> ST s ByteArray
forall s a. STRep s a -> ST s a
ST(STRep s ByteArray -> ST s ByteArray)
-> STRep s ByteArray -> ST s ByteArray
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseMutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray#MutableByteArray# s
mba# State# s
s of(#State# s
s' ,ByteArray#
ba# #)->(#State# s
s' ,ByteArray# -> ByteArray
ByteArrayByteArray#
ba# #)writeWord8Array ::MutableByteArrays ->Int->Word8->STs ()writeWord8Array :: forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array (MutableByteArrayMutableByteArray# s
mba# )(I#Int#
i# )(W8#Word8#
w# )=STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST(STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseMutableByteArray# s -> Int# -> Word8# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
writeWord8Array#MutableByteArray# s
mba# Int#
i# Word8#
w# State# s
s ofState# s
s' ->(#State# s
s' ,()#)
#if HS_UNALIGNED_ByteArray_OPS_OK
writeWord64Array ::MutableByteArrays ->Int->Word64->STs ()writeWord64Array :: forall s. MutableByteArray s -> Int -> Word64 -> ST s ()
writeWord64Array (MutableByteArrayMutableByteArray# s
mba# )(I#Int#
i# )(W64#Word64#
w# )=STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST(STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseMutableByteArray# s -> Int# -> Word64# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
writeWord64Array#MutableByteArray# s
mba# Int#
i# Word64#
w# State# s
s ofState# s
s' ->(#State# s
s' ,()#)
#endif
copyAddrToByteArray ::Ptra ->MutableByteArrayRealWorld->Int->Int->STRealWorld()copyAddrToByteArray :: forall a.
Ptr a
-> MutableByteArray RealWorld -> Int -> Int -> ST RealWorld ()
copyAddrToByteArray (PtrAddr#
src# )(MutableByteArrayMutableByteArray# RealWorld
dst# )(I#Int#
dst_off# )(I#Int#
len# )=STRep RealWorld () -> ST RealWorld ()
forall s a. STRep s a -> ST s a
ST(STRep RealWorld () -> ST RealWorld ())
-> STRep RealWorld () -> ST RealWorld ()
forall a b. (a -> b) -> a -> b
$\State# RealWorld
s ->caseAddr#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
copyAddrToByteArray# Addr#
src# MutableByteArray# RealWorld
dst# Int#
dst_off# Int#
len# State# RealWorld
s ofState# RealWorld
s' ->(#State# RealWorld
s' ,()#)copyByteArrayToAddr ::ByteArray->Int->Ptra ->Int->STRealWorld()copyByteArrayToAddr :: forall a. ByteArray -> Int -> Ptr a -> Int -> ST RealWorld ()
copyByteArrayToAddr (ByteArrayByteArray#
src# )(I#Int#
src_off# )(PtrAddr#
dst# )(I#Int#
len# )=STRep RealWorld () -> ST RealWorld ()
forall s a. STRep s a -> ST s a
ST(STRep RealWorld () -> ST RealWorld ())
-> STRep RealWorld () -> ST RealWorld ()
forall a b. (a -> b) -> a -> b
$\State# RealWorld
s ->caseByteArray#
-> Int# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
copyByteArrayToAddr# ByteArray#
src# Int#
src_off# Addr#
dst# Int#
len# State# RealWorld
s ofState# RealWorld
s' ->(#State# RealWorld
s' ,()#)copyByteArray ::ByteArray->Int->MutableByteArrays ->Int->Int->STs ()copyByteArray :: forall s.
ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyByteArray (ByteArrayByteArray#
src# )(I#Int#
src_off# )(MutableByteArrayMutableByteArray# s
dst# )(I#Int#
dst_off# )(I#Int#
len# )=STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST(STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall s.
ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
copyByteArray# ByteArray#
src# Int#
src_off# MutableByteArray# s
dst# Int#
dst_off# Int#
len# State# s
s ofState# s
s' ->(#State# s
s' ,()#)setByteArray ::MutableByteArrays ->Int->Int->Int->STs ()setByteArray :: forall s. MutableByteArray s -> Int -> Int -> Int -> ST s ()
setByteArray (MutableByteArrayMutableByteArray# s
dst# )(I#Int#
off# )(I#Int#
len# )(I#Int#
c# )=STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST(STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseMutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
setByteArray#MutableByteArray# s
dst# Int#
off# Int#
len# Int#
c# State# s
s ofState# s
s' ->(#State# s
s' ,()#)copyMutableByteArray ::MutableByteArrays ->Int->MutableByteArrays ->Int->Int->STs ()copyMutableByteArray :: forall s.
MutableByteArray s
-> Int -> MutableByteArray s -> Int -> Int -> ST s ()
copyMutableByteArray (MutableByteArrayMutableByteArray# s
src# )(I#Int#
src_off# )(MutableByteArrayMutableByteArray# s
dst# )(I#Int#
dst_off# )(I#Int#
len# )=STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST(STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$\State# s
s ->caseMutableByteArray# s
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray#MutableByteArray# s
src# Int#
src_off# MutableByteArray# s
dst# Int#
dst_off# Int#
len# State# s
s ofState# s
s' ->(#State# s
s' ,()#)-------------------------------------------------------------------------- FFI imports--compareByteArrays ::ByteArray->ByteArray->Int->IntcompareByteArrays :: ByteArray -> ByteArray -> Int -> Int
compareByteArrays ByteArray
ba1 ByteArray
ba2 =ByteArray -> Int -> ByteArray -> Int -> Int -> Int
compareByteArraysOff ByteArray
ba1 Int
0ByteArray
ba2 Int
0compareByteArraysOff ::ByteArray-- ^ array 1->Int-- ^ offset for array 1->ByteArray-- ^ array 2->Int-- ^ offset for array 2->Int-- ^ length to compare->Int-- ^ like memcmpcompareByteArraysOff :: ByteArray -> Int -> ByteArray -> Int -> Int -> Int
compareByteArraysOff (ByteArrayByteArray#
ba1# )(I#Int#
ba1off# )(ByteArrayByteArray#
ba2# )(I#Int#
ba2off# )(I#Int#
len# )=Int# -> Int
I#(ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
compareByteArrays#ByteArray#
ba1# Int#
ba1off# ByteArray#
ba2# Int#
ba2off# Int#
len# )-------------------------------------------------------------------------- Primop replacementscopyAddrToByteArray# ::Addr#->MutableByteArray#RealWorld->Int#->Int#->State#RealWorld->State#RealWorldcopyByteArrayToAddr# ::ByteArray#->Int#->Addr#->Int#->State#RealWorld->State#RealWorldcopyByteArray# ::ByteArray#->Int#->MutableByteArray#s ->Int#->Int#->State#s ->State#s copyAddrToByteArray# :: Addr#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
copyAddrToByteArray# =Addr#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
forall d.
Addr#
-> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
GHC.Exts.copyAddrToByteArray#copyByteArrayToAddr# :: ByteArray#
-> Int# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
copyByteArrayToAddr# =ByteArray#
-> Int# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
forall d.
ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
GHC.Exts.copyByteArrayToAddr#copyByteArray# :: forall s.
ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
copyByteArray# =ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall s.
ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
GHC.Exts.copyByteArray#-- | /O(n)./ Construct a new @ShortByteString@ from a @CString@. The-- resulting @ShortByteString@ is an immutable copy of the original-- @CString@, and is managed on the Haskell heap. The original-- @CString@ must be null terminated.---- @since 0.10.10.0packCString ::CString->IOShortByteString packCString :: CString -> IO ShortByteString
packCString CString
cstr =doCSize
len <-CString -> IO CSize
BS.c_strlen CString
cstr CStringLen -> IO ShortByteString
packCStringLen (CString
cstr ,CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralCSize
len )-- | /O(n)./ Construct a new @ShortByteString@ from a @CStringLen@. The-- resulting @ShortByteString@ is an immutable copy of the original @CStringLen@.-- The @ShortByteString@ is a normal Haskell value and will be managed on the-- Haskell heap.---- @since 0.10.10.0packCStringLen ::CStringLen->IOShortByteString packCStringLen :: CStringLen -> IO ShortByteString
packCStringLen (CString
cstr ,Int
len )|Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0=CString -> Int -> IO ShortByteString
forall a. Ptr a -> Int -> IO ShortByteString
createFromPtr CString
cstr Int
len packCStringLen (CString
_,Int
len )=String -> String -> IO ShortByteString
forall a. HasCallStack => String -> String -> IO a
moduleErrorIO String
"packCStringLen"(String
"negative length: "String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
showInt
len )-- | /O(n) construction./ Use a @ShortByteString@ with a function requiring a-- null-terminated @CString@. The @CString@ is a copy and will be freed-- automatically; it must not be stored or used after the-- subcomputation finishes.---- @since 0.10.10.0useAsCString ::ShortByteString ->(CString->IOa )->IOa useAsCString :: forall a. ShortByteString -> (CString -> IO a) -> IO a
useAsCString ShortByteString
sbs CString -> IO a
action =Int -> (CString -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes(Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\CString
buf ->doShortByteString -> Int -> CString -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
copyToPtr ShortByteString
sbs Int
0CString
buf (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
l )CString -> Int -> Word8 -> IO ()
forall b. Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOffCString
buf Int
l (Word8
0::Word8)CString -> IO a
action CString
buf wherel :: Int
l =ShortByteString -> Int
length ShortByteString
sbs -- | /O(n) construction./ Use a @ShortByteString@ with a function requiring a 'CStringLen'.-- As for 'useAsCString' this function makes a copy of the original @ShortByteString@.-- It must not be stored or used after the subcomputation finishes.---- Beware that this function does not add a terminating @\NUL@ byte at the end of 'CStringLen'.-- If you need to construct a pointer to a null-terminated sequence, use 'useAsCString'-- (and measure length independently if desired).---- @since 0.10.10.0useAsCStringLen ::ShortByteString ->(CStringLen->IOa )->IOa useAsCStringLen :: forall a. ShortByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen ShortByteString
sbs CStringLen -> IO a
action =Int -> (CString -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytesInt
l ((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\CString
buf ->doShortByteString -> Int -> CString -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
copyToPtr ShortByteString
sbs Int
0CString
buf (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
l )CStringLen -> IO a
action (CString
buf ,Int
l )wherel :: Int
l =ShortByteString -> Int
length ShortByteString
sbs -- | /O(n)/ Check whether a 'ShortByteString' represents valid UTF-8.---- @since 0.11.3.0isValidUtf8 ::ShortByteString ->BoolisValidUtf8 :: ShortByteString -> Bool
isValidUtf8 sbs :: ShortByteString
sbs @(SBS ByteArray#
ba# )=IO Bool -> Bool
forall a. IO a -> a
accursedUnutterablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$doletn :: Int
n =ShortByteString -> Int
length ShortByteString
sbs -- Use a safe FFI call for large inputs to avoid GC synchronization pauses-- in multithreaded contexts.-- This specific limit was chosen based on results of a simple benchmark, see:-- https://github.com/haskell/bytestring/issues/451#issuecomment-991879338-- When changing this function, also consider changing the related function:-- Data.ByteString.isValidUtf8CInt
i <-ifInt
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
1000000Bool -> Bool -> Bool
||Bool -> Bool
not(ByteArray# -> Bool
isPinned ByteArray#
ba# )thenByteArray# -> CSize -> IO CInt
cIsValidUtf8BA ByteArray#
ba# (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
n )elseByteArray# -> CSize -> IO CInt
cIsValidUtf8BASafe ByteArray#
ba# (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
n )STRep RealWorld () -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO(\State# RealWorld
s ->(#ByteArray# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch#ByteArray#
ba# State# RealWorld
s ,()#))Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$CInt
i CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/=CInt
0-- ----------------------------------------------------------------------- Internal utilitiesmoduleErrorIO ::HasCallStack=>String->String->IOa moduleErrorIO :: forall a. HasCallStack => String -> String -> IO a
moduleErrorIO String
fun String
msg =IOError -> IO a
forall e a. Exception e => e -> IO a
throwIO(IOError -> IO a) -> (String -> IOError) -> String -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> IOError
userError(String -> IO a) -> String -> IO a
forall a b. (a -> b) -> a -> b
$String -> ShowS
moduleErrorMsg String
fun String
msg {-# NOINLINEmoduleErrorIO #-}moduleErrorMsg ::String->String->StringmoduleErrorMsg :: String -> ShowS
moduleErrorMsg String
fun String
msg =String
"Data.ByteString.Short."String -> ShowS
forall a. [a] -> [a] -> [a]
++String
fun String -> ShowS
forall a. [a] -> [a] -> [a]
++Char
':'Char -> ShowS
forall a. a -> [a] -> [a]
:Char
' 'Char -> ShowS
forall a. a -> [a] -> [a]
:String
msg -- Find from the end of the string using predicate.---- Return '0' if the predicate returns false for the entire ShortByteString.findFromEndUntil ::(Word8->Bool)->ShortByteString ->IntfindFromEndUntil :: (Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil Word8 -> Bool
k ShortByteString
sbs =Int -> Int
go (ShortByteString -> Int
length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)whereba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs go :: Int -> Int
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
0=Int
0|Word8 -> Bool
k (ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba Int
n )=Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1|Bool
otherwise=Int -> Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)findIndexOrLength ::(Word8->Bool)->ShortByteString ->IntfindIndexOrLength :: (Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength Word8 -> Bool
k ShortByteString
sbs =Int -> Int
go Int
0wherel :: Int
l =ShortByteString -> Int
length ShortByteString
sbs ba :: ByteArray
ba =ShortByteString -> ByteArray
asBA ShortByteString
sbs go :: Int -> Int
go !Int
n |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
l =Int
l |Word8 -> Bool
k (ByteArray -> Int -> Word8
indexWord8Array ByteArray
ba Int
n )=Int
n |Bool
otherwise=Int -> Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)packBytesRev ::[Word8]->ShortByteString packBytesRev :: [Word8] -> ShortByteString
packBytesRev [Word8]
cs =Int -> [Word8] -> ShortByteString
packLenBytesRev ([Word8] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.length[Word8]
cs )[Word8]
cs packLenBytesRev ::Int->[Word8]->ShortByteString packLenBytesRev :: Int -> [Word8] -> ShortByteString
packLenBytesRev Int
len [Word8]
ws0 =Int -> (forall s. MutableByteArray s -> ST s ()) -> ShortByteString
create Int
len (\MutableByteArray s
mba ->MutableByteArray s -> Int -> [Word8] -> ST s ()
forall s. MutableByteArray s -> Int -> [Word8] -> ST s ()
go MutableByteArray s
mba Int
len [Word8]
ws0 )wherego ::MutableByteArrays ->Int->[Word8]->STs ()go :: forall s. MutableByteArray s -> Int -> [Word8] -> ST s ()
go !MutableByteArray s
_!Int
_[]=() -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return()go !MutableByteArray s
mba !Int
i (Word8
w :[Word8]
ws )=doMutableByteArray s -> Int -> Word8 -> ST s ()
forall s. MutableByteArray s -> Int -> Word8 -> ST s ()
writeWord8Array MutableByteArray s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)Word8
w MutableByteArray s -> Int -> [Word8] -> ST s ()
forall s. MutableByteArray s -> Int -> [Word8] -> ST s ()
go MutableByteArray s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)[Word8]
ws breakByte ::Word8->ShortByteString ->(ShortByteString ,ShortByteString )breakByte :: Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte Word8
c ShortByteString
sbs =caseWord8 -> ShortByteString -> Maybe Int
elemIndex Word8
c ShortByteString
sbs ofMaybe Int
Nothing->(ShortByteString
sbs ,ShortByteString
empty )JustInt
n ->(Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
sbs ,Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
sbs )-- Common up near identical calls to `error' to reduce the number-- constant strings created when compiled:errorEmptySBS ::HasCallStack=>String->a errorEmptySBS :: forall a. HasCallStack => String -> a
errorEmptySBS String
fun =String -> String -> a
forall a. HasCallStack => String -> String -> a
moduleError String
fun String
"empty ShortByteString"{-# NOINLINEerrorEmptySBS #-}moduleError ::HasCallStack=>String->String->a moduleError :: forall a. HasCallStack => String -> String -> a
moduleError String
fun String
msg =String -> a
forall a. HasCallStack => String -> a
error(String -> ShowS
moduleErrorMsg String
fun String
msg ){-# NOINLINEmoduleError #-}