{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE Unsafe #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fexpose-all-unfoldings #-}
{-# OPTIONS_HADDOCK not-home #-}
#if defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH) \
|| ((defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) \
&& defined(__ARM_FEATURE_UNALIGNED)) \
|| defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
|| defined(powerpc64le_HOST_ARCH)
#define SAFE_UNALIGNED 1
#endif
module System.AbstractFilePath.Data.ByteString.Short (
ShortByteString(..),
empty,
singleton,
pack,
unpack,
fromShort,
toShort,
snoc,
cons,
append,
last,
tail,
uncons,
head,
init,
unsnoc,
null,
length,
map,
reverse,
intercalate,
foldl,
foldl',
foldl1,
foldl1',
foldr,
foldr',
foldr1,
foldr1',
all,
any,
concat,
replicate,
unfoldr,
unfoldrN,
take,
takeEnd,
takeWhileEnd,
takeWhile,
drop,
dropEnd,
dropWhile,
dropWhileEnd,
breakEnd,
break,
span,
spanEnd,
splitAt,
split,
splitWith,
stripSuffix,
stripPrefix,
isInfixOf,
isPrefixOf,
isSuffixOf,
breakSubstring,
elem,
find,
filter,
partition,
index,
indexMaybe,
(!?),
elemIndex,
elemIndices,
count,
findIndex,
findIndices,
packCString,
packCStringLen,
useAsCString,
useAsCStringLen,
) where
import Prelude ()
#if MIN_VERSION_bytestring(0,11,3)
import Data.ByteString.Short.Internal
#else
#if !MIN_VERSION_base(4,11,0)
import System.IO.Unsafe
( unsafeDupablePerformIO )
#endif
import Data.ByteString.Short.Internal (
ShortByteString(..)
#if !MIN_VERSION_bytestring(0,10,9)
, copyToPtr
, createFromPtr
#endif
)
import Data.ByteString.Short
#if MIN_VERSION_bytestring(0,10,9)
import Data.ByteString.Internal
( checkedAdd
)
#endif
import Data.Bits
( FiniteBits (finiteBitSize)
, shiftL
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
, shiftR
#endif
, (.&.)
, (.|.)
)
import Control.Applicative
( pure )
import Control.Exception
( assert
#if !MIN_VERSION_bytestring(0,10,10)
, throwIO
#endif
,
)
import Control.Monad
( (>>) )
#if !MIN_VERSION_bytestring(0,10,10)
import Foreign.C.String
( CString
, CStringLen
)
#endif
#if !MIN_VERSION_base(4,11,0)
import Foreign.Ptr
( plusPtr )
import Foreign.Marshal.Alloc
( free
, mallocBytes
)
#endif
#if !MIN_VERSION_bytestring(0,10,9)
import Foreign.Marshal.Alloc
( allocaBytes )
import Foreign.Storable
( pokeByteOff )
#endif
import GHC.Exts
( Int(I#), Int#
, State#
, ByteArray#, MutableByteArray#
, newByteArray#
, copyMutableByteArray#
#if MIN_VERSION_base(4,11,0)
, compareByteArrays#
#endif
, indexWord8Array#
, writeWord8Array#
, unsafeFreezeByteArray#
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
,writeWord64Array#
,indexWord8ArrayAsWord64#
#endif
, setByteArray#
, indexWord8Array#
, writeWord8Array#
, unsafeFreezeByteArray#
)
import GHC.ST
( ST(ST)
, runST
)
import GHC.Stack.Types
( HasCallStack )
import GHC.Word
import Prelude
( Eq(..), Ord(..)
, ($), ($!), error, (++), (.), (||)
, String
, Bool(..), (&&), otherwise
, (+), (-), fromIntegral
, (*)
, (^)
, return
, Maybe(..)
, not
, snd
#if !MIN_VERSION_bytestring(0,10,9)
, show
#endif
#if !MIN_VERSION_bytestring(0,10,10)
, userError
, IO
#endif
)
#if !MIN_VERSION_bytestring(0,10,10)
import qualified Data.ByteString.Internal as BS
#endif
import qualified Data.Foldable as Foldable
import qualified Data.List as List
import qualified GHC.Exts
#if !MIN_VERSION_bytestring(0,11,0)
indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe ShortByteString
sbs Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> 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
{-# INLINE indexMaybe #-}
(!?) :: ShortByteString -> Int -> Maybe Word8
!? :: ShortByteString -> Int -> Maybe Word8
(!?) = ShortByteString -> Int -> Maybe Word8
indexMaybe
{-# INLINE (!?) #-}
#endif
unsafeIndex :: ShortByteString -> Int -> Word8
unsafeIndex :: ShortByteString -> Int -> Word8
unsafeIndex ShortByteString
sbs = BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs)
asBA :: ShortByteString -> BA
asBA :: ShortByteString -> BA
asBA (SBS ByteArray#
ba#) = ByteArray# -> BA
BA# ByteArray#
ba#
create :: Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create :: Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
len forall s. MBA s -> ST s ()
fill =
(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
$ do
MBA s
mba <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
len
MBA s -> ST s ()
forall s. MBA s -> ST s ()
fill MBA s
mba
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba
ShortByteString -> ST s ShortByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#)
{-# INLINE create #-}
createAndTrim :: Int -> (forall s. MBA s -> ST s (Int, a)) -> (ShortByteString, a)
createAndTrim :: Int -> (forall s. MBA s -> ST s (Int, a)) -> (ShortByteString, a)
createAndTrim Int
l forall s. MBA s -> ST s (Int, a)
fill =
(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
$ do
MBA s
mba <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l
(Int
l', a
res) <- MBA s -> ST s (Int, a)
forall s. MBA s -> ST s (Int, a)
fill MBA s
mba
if Bool -> Bool -> Bool
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l) (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l
then do
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba
(ShortByteString, a) -> ST s (ShortByteString, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#, a
res)
else do
MBA s
mba2 <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l'
MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
copyMutableByteArray MBA s
mba Int
0 MBA s
mba2 Int
0 Int
l'
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba2
(ShortByteString, a) -> ST s (ShortByteString, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#, a
res)
{-# INLINE createAndTrim #-}
createAndTrim' :: Int -> (forall s. MBA s -> ST s Int) -> ShortByteString
createAndTrim' :: Int -> (forall s. MBA s -> ST s Int) -> ShortByteString
createAndTrim' Int
l forall s. MBA s -> ST s Int
fill =
(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
$ do
MBA s
mba <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l
Int
l' <- MBA s -> ST s Int
forall s. MBA s -> ST s Int
fill MBA s
mba
if Bool -> Bool -> Bool
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l) (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l
then do
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba
ShortByteString -> ST s ShortByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#)
else do
MBA s
mba2 <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l'
MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
copyMutableByteArray MBA s
mba Int
0 MBA s
mba2 Int
0 Int
l'
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba2
ShortByteString -> ST s ShortByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#)
{-# INLINE createAndTrim' #-}
createAndTrim'' :: Int -> (forall s. MBA s -> MBA s -> ST s (Int, Int)) -> (ShortByteString, ShortByteString)
createAndTrim'' :: Int
-> (forall s. MBA s -> MBA s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
createAndTrim'' Int
l forall s. MBA s -> MBA 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
$ do
MBA s
mba1 <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l
MBA s
mba2 <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l
(Int
l1, Int
l2) <- MBA s -> MBA s -> ST s (Int, Int)
forall s. MBA s -> MBA s -> ST s (Int, Int)
fill MBA s
mba1 MBA s
mba2
ShortByteString
sbs1 <- Int -> MBA s -> ST s ShortByteString
forall s. Int -> MBA s -> ST s ShortByteString
freeze' Int
l1 MBA s
mba1
ShortByteString
sbs2 <- Int -> MBA s -> ST s ShortByteString
forall s. Int -> MBA s -> ST s ShortByteString
freeze' Int
l2 MBA s
mba2
(ShortByteString, ShortByteString)
-> ST s (ShortByteString, ShortByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortByteString
sbs1, ShortByteString
sbs2)
where
freeze' :: Int -> MBA s -> ST s ShortByteString
freeze' :: Int -> MBA s -> ST s ShortByteString
freeze' Int
l' MBA s
mba =
if Bool -> Bool -> Bool
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l) (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l
then do
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba
ShortByteString -> ST s ShortByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#)
else do
MBA s
mba2 <- Int -> ST s (MBA s)
forall s. Int -> ST s (MBA s)
newByteArray Int
l'
MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
copyMutableByteArray MBA s
mba Int
0 MBA s
mba2 Int
0 Int
l'
BA# ByteArray#
ba# <- MBA s -> ST s BA
forall s. MBA s -> ST s BA
unsafeFreezeByteArray MBA s
mba2
ShortByteString -> ST s ShortByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS ByteArray#
ba#)
{-# INLINE createAndTrim'' #-}
singleton :: Word8 -> ShortByteString
singleton :: Word8 -> ShortByteString
singleton = \Word8
w -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
1 (\MBA s
mba -> MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
0 Word8
w)
append :: 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
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create (Int
len1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len2) ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
dst -> do
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
src1) Int
0 MBA s
dst Int
0 Int
len1
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
src2) Int
0 MBA s
dst Int
len1 Int
len2
concat :: [ShortByteString] -> ShortByteString
concat :: [ShortByteString] -> ShortByteString
concat = \[ShortByteString]
sbss ->
Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create (Int -> [ShortByteString] -> Int
totalLen Int
0 [ShortByteString]
sbss) (\MBA s
dst -> MBA s -> Int -> [ShortByteString] -> ST s ()
forall s. MBA s -> Int -> [ShortByteString] -> ST s ()
copy MBA s
dst Int
0 [ShortByteString]
sbss)
where
totalLen :: Int -> [ShortByteString] -> Int
totalLen !Int
acc [] = Int
acc
totalLen !Int
acc (ShortByteString
sbs: [ShortByteString]
sbss) = Int -> [ShortByteString] -> Int
totalLen (Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ShortByteString -> Int
length ShortByteString
sbs) [ShortByteString]
sbss
copy :: MBA s -> Int -> [ShortByteString] -> ST s ()
copy :: MBA s -> Int -> [ShortByteString] -> ST s ()
copy !MBA s
_ !Int
_ [] = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
copy !MBA s
dst !Int
off (ShortByteString
src : [ShortByteString]
sbss) = do
let !len :: Int
len = ShortByteString -> Int
length ShortByteString
src
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
src) Int
0 MBA s
dst Int
off Int
len
MBA s -> Int -> [ShortByteString] -> ST s ()
forall s. MBA s -> Int -> [ShortByteString] -> ST s ()
copy MBA s
dst (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) [ShortByteString]
sbss
infixr 5 `cons`
infixl 5 `snoc`
snoc :: ShortByteString -> Word8 -> ShortByteString
snoc :: ShortByteString -> Word8 -> ShortByteString
snoc = \ShortByteString
sbs Word8
c -> let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
l
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
l Word8
c
cons :: Word8 -> ShortByteString -> ShortByteString
cons :: Word8 -> ShortByteString -> ShortByteString
cons Word8
c = \ShortByteString
sbs -> let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
0 Word8
c
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
1 Int
l
last :: HasCallStack => ShortByteString -> Word8
last :: ShortByteString -> Word8
last = \ShortByteString
sbs -> case ShortByteString -> Bool
null ShortByteString
sbs of
Bool
True -> String -> Word8
forall a. (?callStack::CallStack) => String -> a
errorEmptySBS String
"last"
Bool
False -> BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) (ShortByteString -> Int
length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
tail :: HasCallStack => ShortByteString -> ShortByteString
tail :: ShortByteString -> ShortByteString
tail = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
in case ShortByteString -> Bool
null ShortByteString
sbs of
Bool
True -> String -> ShortByteString
forall a. (?callStack::CallStack) => String -> a
errorEmptySBS String
"tail"
Bool
False -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
1 MBA s
mba Int
0 Int
nl
uncons :: ShortByteString -> Maybe (Word8, ShortByteString)
uncons :: ShortByteString -> Maybe (Word8, ShortByteString)
uncons = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
in if | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> Maybe (Word8, ShortByteString)
forall a. Maybe a
Nothing
| Bool
otherwise -> let h :: Word8
h = BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0
t :: ShortByteString
t = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
1 MBA s
mba Int
0 Int
nl
in (Word8, ShortByteString) -> Maybe (Word8, ShortByteString)
forall a. a -> Maybe a
Just (Word8
h, ShortByteString
t)
head :: HasCallStack => ShortByteString -> Word8
head :: ShortByteString -> Word8
head = \ShortByteString
sbs -> case ShortByteString -> Bool
null ShortByteString
sbs of
Bool
True -> String -> Word8
forall a. (?callStack::CallStack) => String -> a
errorEmptySBS String
"head"
Bool
False -> BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0
init :: HasCallStack => ShortByteString -> ShortByteString
init :: ShortByteString -> ShortByteString
init = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
in case ShortByteString -> Bool
null ShortByteString
sbs of
Bool
True -> String -> ShortByteString
forall a. (?callStack::CallStack) => String -> a
errorEmptySBS String
"init"
Bool
False -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
nl
unsnoc :: ShortByteString -> Maybe (ShortByteString, Word8)
unsnoc :: ShortByteString -> Maybe (ShortByteString, Word8)
unsnoc = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
in if | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> Maybe (ShortByteString, Word8)
forall a. Maybe a
Nothing
| Bool
otherwise -> let l' :: Word8
l' = BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
i :: ShortByteString
i = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
nl
in (ShortByteString, Word8) -> Maybe (ShortByteString, Word8)
forall a. a -> Maybe a
Just (ShortByteString
i, Word8
l')
map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString
map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString
map Word8 -> Word8
f = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
l (\MBA s
mba -> BA -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba Int
0 Int
l)
where
go :: BA -> MBA s -> Int -> Int -> ST s ()
go :: BA -> MBA s -> Int -> Int -> ST s ()
go !BA
ba !MBA s
mba !Int
i !Int
l
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
let w :: Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba Int
i
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
i (Word8 -> Word8
f Word8
w)
BA -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
l
reverse :: ShortByteString -> ShortByteString
reverse :: ShortByteString -> ShortByteString
reverse = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
l (\MBA s
mba -> BA -> MBA s -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> ST s ()
go BA
ba MBA s
mba Int
l)
where
go :: forall s. BA -> MBA s -> Int -> ST s ()
go :: BA -> MBA s -> Int -> ST s ()
go !BA
ba !MBA s
mba !Int
l = do
let q :: Int
q = Int
l Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
3
r :: Int
r = Int
l Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
7
Int
i' <- Int -> Int -> ST s Int
goWord8Chunk Int
0 Int
r
Int -> Int -> Int -> ST s ()
goWord64Chunk Int
i' Int
0 Int
q
where
goWord64Chunk :: Int -> Int -> Int -> ST s ()
goWord64Chunk :: Int -> Int -> Int -> ST s ()
goWord64Chunk !Int
off !Int
i' !Int
cl = Int -> ST s ()
loop Int
i'
where
loop :: Int -> ST s ()
loop :: Int -> ST s ()
loop !Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
cl = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
let w :: Word64
w = BA -> Int -> Word64
indexWord8ArrayAsWord64 BA
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))
MBA s -> Int -> Word64 -> ST s ()
forall s. MBA s -> Int -> Word64 -> ST s ()
writeWord64Array MBA s
mba (Int
cl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) (Word64 -> Word64
byteSwap64 Word64
w)
Int -> ST s ()
loop (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
goWord8Chunk :: Int -> Int -> ST s Int
goWord8Chunk :: Int -> Int -> ST s Int
goWord8Chunk !Int
i' !Int
cl = Int -> ST s Int
loop Int
i'
where
loop :: Int -> ST s Int
loop :: 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 (m :: * -> *) a. Monad m => a -> m a
return Int
i
| Bool
otherwise = do
let w :: Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba Int
i
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) Word8
w
Int -> ST s Int
loop (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
#else
in create l (\mba -> go ba mba 0 l)
where
go :: BA -> MBA s -> Int -> Int -> ST s ()
go !ba !mba !i !l
| i >= l = return ()
| otherwise = do
let w = indexWord8Array ba i
writeWord8Array mba (l - 1 - i) w
go ba mba (i+1) l
#endif
intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString
intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString
intercalate ShortByteString
sep = \case
[] -> ShortByteString
empty
[ShortByteString
x] -> ShortByteString
x
(ShortByteString
sbs:[ShortByteString]
t) -> let !totalLen :: Int
totalLen = (Int -> ShortByteString -> Int) -> Int -> [ShortByteString] -> Int
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
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
totalLen (\MBA s
mba ->
let !l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
in BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
l ST s () -> ST s () -> ST s ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> Int -> [ShortByteString] -> ST s ()
forall s. MBA s -> Int -> [ShortByteString] -> ST s ()
go MBA s
mba Int
l [ShortByteString]
t)
where
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sep
lba :: Int
lba = ShortByteString -> Int
length ShortByteString
sep
go :: MBA s -> Int -> [ShortByteString] -> ST s ()
go :: MBA s -> Int -> [ShortByteString] -> ST s ()
go MBA s
_ Int
_ [] = () -> ST s ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
go MBA s
mba !Int
off (ShortByteString
chunk:[ShortByteString]
chunks) = do
let lc :: Int
lc = ShortByteString -> Int
length ShortByteString
chunk
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray BA
ba Int
0 MBA s
mba Int
off Int
lba
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
chunk) Int
0 MBA s
mba (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lba) Int
lc
MBA s -> Int -> [ShortByteString] -> ST s ()
forall s. MBA s -> Int -> [ShortByteString] -> ST s ()
go MBA 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"
foldl :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl a -> Word8 -> a
f a
v = (a -> Word8 -> a) -> a -> [Word8] -> a
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
foldl' :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' a -> Word8 -> a
f a
v = (a -> Word8 -> a) -> a -> [Word8] -> a
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 :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr Word8 -> a -> a
f a
v = (Word8 -> a -> a) -> a -> [Word8] -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
List.foldr Word8 -> a -> a
f a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
foldr' :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' Word8 -> a -> a
k a
v = (Word8 -> a -> a) -> a -> [Word8] -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr' Word8 -> a -> a
k a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1 :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1 Word8 -> Word8 -> Word8
k = (Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t 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
foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1' :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1' Word8 -> Word8 -> Word8
k = (Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall a. (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 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1 :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1 Word8 -> Word8 -> Word8
k = (Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldr1 Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1' :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1' Word8 -> Word8 -> Word8
k = \ShortByteString
sbs -> if ShortByteString -> Bool
null ShortByteString
sbs then String -> Word8
forall a. (?callStack::CallStack) => 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 ((?callStack::CallStack) => ShortByteString -> Word8
ShortByteString -> Word8
last ShortByteString
sbs) ((?callStack::CallStack) => ShortByteString -> ShortByteString
ShortByteString -> ShortByteString
init ShortByteString
sbs)
all :: (Word8 -> Bool) -> ShortByteString -> Bool
all :: (Word8 -> Bool) -> ShortByteString -> Bool
all Word8 -> Bool
k = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
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)
in Int -> Bool
go Int
0
any :: (Word8 -> Bool) -> ShortByteString -> Bool
any :: (Word8 -> Bool) -> ShortByteString -> Bool
any Word8 -> Bool
k = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
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)
in Int -> Bool
go Int
0
take :: Int -> ShortByteString -> ShortByteString
take :: Int -> ShortByteString -> ShortByteString
take = \Int
n -> \ShortByteString
sbs -> let sl :: Int
sl = ShortByteString -> Int
length ShortByteString
sbs
in if | 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. MBA s -> ST s ()) -> ShortByteString
create Int
n ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
n
takeWhile :: (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
takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd Int
n = \ShortByteString
sbs -> let sl :: Int
sl = ShortByteString -> Int
length ShortByteString
sbs
in if | 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. MBA s -> ST s ()) -> ShortByteString
create Int
n ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
sl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)) MBA s
mba Int
0 Int
n
takeWhileEnd :: (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
drop :: Int -> ShortByteString -> ShortByteString
drop :: Int -> ShortByteString -> ShortByteString
drop = \Int
n -> \ShortByteString
sbs ->
let len :: Int
len = ShortByteString -> Int
length ShortByteString
sbs
in if | 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 ->
let newLen :: Int
newLen = Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n
in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
newLen ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
n MBA s
mba Int
0 Int
newLen
dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd Int
n = \ShortByteString
sbs -> let sl :: Int
sl = ShortByteString -> Int
length ShortByteString
sbs
nl :: Int
nl = Int
sl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n
in if | 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. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
nl
dropWhile :: (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
dropWhileEnd :: (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
breakEnd :: (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
break :: (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 of Int
n -> (Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
sbs, Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
sbs)
span :: (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)
spanEnd :: (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
splitAt :: 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 ->
let slen :: Int
slen = ShortByteString -> Int
length ShortByteString
sbs
in if | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= ShortByteString -> Int
length ShortByteString
sbs -> (ShortByteString
sbs, ShortByteString
empty)
| Bool
otherwise ->
let llen :: Int
llen = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
slen (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
n)
rlen :: Int
rlen = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
slen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
n)
lsbs :: ShortByteString
lsbs = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
llen ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
llen
rsbs :: ShortByteString
rsbs = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
rlen ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
n MBA s
mba Int
0 Int
rlen
in (ShortByteString
lsbs, ShortByteString
rsbs)
split :: 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)
splitWith :: (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
where
go :: 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 ((?callStack::CallStack) => ShortByteString -> ShortByteString
ShortByteString -> ShortByteString
tail ShortByteString
b)
stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripSuffix ShortByteString
sbs1 = \ShortByteString
sbs2 -> do
let l1 :: Int
l1 = ShortByteString -> Int
length ShortByteString
sbs1
l2 :: Int
l2 = ShortByteString -> Int
length ShortByteString
sbs2
if | ShortByteString -> ShortByteString -> Bool
isSuffixOf ShortByteString
sbs1 ShortByteString
sbs2 ->
if ShortByteString -> Bool
null ShortByteString
sbs1
then ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just ShortByteString
sbs2
else ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just (ShortByteString -> Maybe ShortByteString)
-> ShortByteString -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$! Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1) ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
dst -> do
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs2) Int
0 MBA 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
stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripPrefix ShortByteString
sbs1 = \ShortByteString
sbs2 -> do
let l1 :: Int
l1 = ShortByteString -> Int
length ShortByteString
sbs1
l2 :: Int
l2 = ShortByteString -> Int
length ShortByteString
sbs2
if | ShortByteString -> ShortByteString -> Bool
isPrefixOf ShortByteString
sbs1 ShortByteString
sbs2 ->
if ShortByteString -> Bool
null ShortByteString
sbs1
then ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just ShortByteString
sbs2
else ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just (ShortByteString -> Maybe ShortByteString)
-> ShortByteString -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$! Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1) ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
dst -> do
BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs2) Int
l1 MBA 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
replicate :: 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. MBA s -> ST s ()) -> ShortByteString
create Int
w (\MBA s
mba -> MBA s -> Int -> Int -> Int -> ST s ()
forall s. MBA s -> Int -> Int -> Int -> ST s ()
setByteArray MBA s
mba Int
0 Int
w (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c))
unfoldr :: (a -> Maybe (Word8, a)) -> a -> ShortByteString
unfoldr :: (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 []
where
go :: a -> [Word8] -> [Word8]
go a
x [Word8]
words' = case a -> Maybe (Word8, a)
f a
x of
Maybe (Word8, a)
Nothing -> [Word8]
words'
Just (Word8
w, a
x') -> a -> [Word8] -> [Word8]
go a
x' (Word8
wWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
words')
unfoldrN :: forall a. Int -> (a -> Maybe (Word8, a)) -> a -> (ShortByteString, Maybe a)
unfoldrN :: 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
Just a
x0)
| Bool
otherwise -> Int
-> (forall s. MBA s -> ST s (Int, Maybe a))
-> (ShortByteString, Maybe a)
forall a.
Int -> (forall s. MBA s -> ST s (Int, a)) -> (ShortByteString, a)
createAndTrim Int
i ((forall s. MBA s -> ST s (Int, Maybe a))
-> (ShortByteString, Maybe a))
-> (forall s. MBA s -> ST s (Int, Maybe a))
-> (ShortByteString, Maybe a)
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> a -> Int -> ST s (Int, Maybe a)
forall s. MBA s -> a -> Int -> ST s (Int, Maybe a)
go MBA s
mba a
x0 Int
0
where
go :: forall s. MBA s -> a -> Int -> ST s (Int, Maybe a)
go :: MBA s -> a -> Int -> ST s (Int, Maybe a)
go !MBA s
mba !a
x !Int
n = a -> Int -> ST s (Int, Maybe a)
go' a
x Int
n
where
go' :: a -> Int -> ST s (Int, Maybe a)
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 (m :: * -> *) a. Monad m => a -> m a
return (Int
n', a -> Maybe a
forall a. a -> Maybe a
Just a
x')
| Bool
otherwise = case a -> Maybe (Word8, a)
f a
x' of
Maybe (Word8, a)
Nothing -> (Int, Maybe a) -> ST s (Int, Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n', Maybe a
forall a. Maybe a
Nothing)
Just (Word8
w, a
x'') -> do
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA 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)
isInfixOf :: ShortByteString -> ShortByteString -> Bool
isInfixOf :: 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.inline ShortByteString
-> ShortByteString -> (ShortByteString, ShortByteString)
breakSubstring) ShortByteString
sbs ShortByteString
s)
isPrefixOf :: ShortByteString -> ShortByteString -> Bool
#if MIN_VERSION_base(4,11,0)
isPrefixOf :: ShortByteString -> ShortByteString -> Bool
isPrefixOf ShortByteString
sbs1 = \ShortByteString
sbs2 -> do
let l1 :: 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 ->
let i :: Int
i = BA -> Int -> BA -> Int -> Int -> Int
compareByteArraysOff (ShortByteString -> BA
asBA ShortByteString
sbs1) Int
0 (ShortByteString -> BA
asBA ShortByteString
sbs2) Int
0 Int
l1
in Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
#else
isPrefixOf sbs1 sbs2 =
let l1 = length sbs1
l2 = length sbs2
in if | l1 == 0 -> True
| l2 < l1 -> False
| otherwise -> unsafeDupablePerformIO $ do
p1 <- mallocBytes l1
p2 <- mallocBytes l2
copyToPtr sbs1 0 p1 l1
copyToPtr sbs2 0 p2 l2
i <- BS.memcmp p1 p2 (fromIntegral l1)
free p1
free p2
return $! i == 0
#endif
isSuffixOf :: ShortByteString -> ShortByteString -> Bool
#if MIN_VERSION_base(4,11,0)
isSuffixOf :: ShortByteString -> ShortByteString -> Bool
isSuffixOf ShortByteString
sbs1 = \ShortByteString
sbs2 -> do
let l1 :: 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 ->
let i :: Int
i = BA -> Int -> BA -> Int -> Int -> Int
compareByteArraysOff (ShortByteString -> BA
asBA ShortByteString
sbs1) Int
0 (ShortByteString -> BA
asBA ShortByteString
sbs2) (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1) Int
l1
in Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
#else
isSuffixOf sbs1 sbs2 =
let l1 = length sbs1
l2 = length sbs2
in if | l1 == 0 -> True
| l2 < l1 -> False
| otherwise -> unsafeDupablePerformIO $ do
p1 <- mallocBytes l1
p2 <- mallocBytes l2
copyToPtr sbs1 0 p1 l1
copyToPtr sbs2 0 p2 l2
i <- BS.memcmp p1 (p2 `plusPtr` (l2 - l1)) (fromIntegral l1)
free p1
free p2
return $! i == 0
#endif
breakSubstring :: ShortByteString
-> ShortByteString
-> (ShortByteString, ShortByteString)
breakSubstring :: ShortByteString
-> ShortByteString -> (ShortByteString, ShortByteString)
breakSubstring ShortByteString
pat =
case Int
lp of
Int
0 -> (ShortByteString
empty,)
Int
1 -> Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte ((?callStack::CallStack) => ShortByteString -> Word8
ShortByteString -> Word8
head ShortByteString
pat)
Int
_ -> if Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Word -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Word
0 :: Word)
then ShortByteString -> (ShortByteString, ShortByteString)
shift
else ShortByteString -> (ShortByteString, ShortByteString)
karpRabin
where
lp :: 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
where
k :: Word32
k = Word32
2891336453 :: Word32
rollingHash :: 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
fromIntegral Word8
b) Word32
0
hp :: 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)
| Bool
otherwise = Word32 -> Int -> (ShortByteString, ShortByteString)
search Word32
hs' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
where
u :: (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)
{-# INLINE karpRabin #-}
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
where
intoWord :: ShortByteString -> Word
intoWord :: 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
fromIntegral Word8
b) Word
0
wp :: Word
wp = ShortByteString -> Word
intoWord ShortByteString
pat
mask' :: Word
mask' = (Word
1 Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
lp)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1
search :: 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)
where
b :: 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)
{-# INLINE shift #-}
elem :: Word8 -> ShortByteString -> Bool
elem :: Word8 -> ShortByteString -> Bool
elem Word8
c = \ShortByteString
sbs -> case Word8 -> ShortByteString -> Maybe Int
elemIndex Word8
c ShortByteString
sbs of Maybe Int
Nothing -> Bool
False ; Maybe Int
_ -> Bool
True
filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
filter Word8 -> Bool
k = \ShortByteString
sbs -> let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
in if | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> ShortByteString
sbs
| Bool
otherwise -> Int -> (forall s. MBA s -> ST s Int) -> ShortByteString
createAndTrim' Int
l ((forall s. MBA s -> ST s Int) -> ShortByteString)
-> (forall s. MBA s -> ST s Int) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> BA -> Int -> ST s Int
forall s. MBA s -> BA -> Int -> ST s Int
go MBA s
mba (ShortByteString -> BA
asBA ShortByteString
sbs) Int
l
where
go :: forall s. MBA s
-> BA
-> Int
-> ST s Int
go :: MBA s -> BA -> Int -> ST s Int
go !MBA s
mba BA
ba !Int
l = Int -> Int -> ST s Int
go' Int
0 Int
0
where
go' :: Int
-> Int
-> ST s Int
go' :: 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 (m :: * -> *) a. Monad m => a -> m a
return Int
bw
| Bool
otherwise = do
let w :: Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba Int
br
if Word8 -> Bool
k Word8
w
then do
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
bw Word8
w
Int -> Int -> ST s Int
go' (Int
brInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
bwInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
else
Int -> Int -> ST s Int
go' (Int
brInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
bw
find :: (Word8 -> Bool) -> ShortByteString -> Maybe Word8
find :: (Word8 -> Bool) -> ShortByteString -> Maybe Word8
find Word8 -> Bool
f = \ShortByteString
sbs -> case (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word8 -> Bool
f ShortByteString
sbs of
Just Int
n -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (ShortByteString
sbs ShortByteString -> Int -> Word8
`index` Int
n)
Maybe Int
_ -> Maybe Word8
forall a. Maybe a
Nothing
partition :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
partition :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
partition Word8 -> Bool
k = \ShortByteString
sbs -> let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
in if | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> (ShortByteString
sbs, ShortByteString
sbs)
| Bool
otherwise -> Int
-> (forall s. MBA s -> MBA s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
createAndTrim'' Int
l ((forall s. MBA s -> MBA s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString))
-> (forall s. MBA s -> MBA s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
forall a b. (a -> b) -> a -> b
$ \MBA s
mba1 MBA s
mba2 -> MBA s -> MBA s -> BA -> Int -> ST s (Int, Int)
forall s. MBA s -> MBA s -> BA -> Int -> ST s (Int, Int)
go MBA s
mba1 MBA s
mba2 (ShortByteString -> BA
asBA ShortByteString
sbs) Int
l
where
go :: forall s.
MBA s
-> MBA s
-> BA
-> Int
-> ST s (Int, Int)
go :: MBA s -> MBA s -> BA -> Int -> ST s (Int, Int)
go !MBA s
mba1 !MBA s
mba2 BA
ba !Int
l = Int -> Int -> ST s (Int, Int)
go' Int
0 Int
0
where
go' :: Int
-> Int
-> ST s (Int, Int)
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 (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 = do
let w :: Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba Int
br
if Word8 -> Bool
k Word8
w
then do
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba1 Int
bw1 Word8
w
Int -> Int -> ST s (Int, Int)
go' (Int
brInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
bw1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
else do
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA 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
brInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
bw1
elemIndex :: Word8 -> ShortByteString -> Maybe Int
elemIndex :: Word8 -> ShortByteString -> Maybe Int
elemIndex Word8
k = (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
k)
elemIndices :: 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 :: Word8 -> ShortByteString -> Int
count :: Word8 -> ShortByteString -> Int
count Word8
w = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.length ([Int] -> Int)
-> (ShortByteString -> [Int]) -> ShortByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ShortByteString -> [Int]
elemIndices Word8
w
findIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word8 -> Bool
k = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
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
Just Int
n
| Bool
otherwise = Int -> Maybe Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
in Int -> Maybe Int
go Int
0
findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices Word8 -> Bool
k = \ShortByteString
sbs ->
let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
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)
in Int -> [Int]
go Int
0
data BA = BA# ByteArray#
data MBA s = MBA# (MutableByteArray# s)
indexWord8Array :: BA -> Int -> Word8
indexWord8Array :: BA -> Int -> Word8
indexWord8Array (BA# ByteArray#
ba#) (I# Int#
i#) = Word# -> Word8
W8# (ByteArray# -> Int# -> Word#
indexWord8Array# ByteArray#
ba# Int#
i#)
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
indexWord8ArrayAsWord64 :: BA -> Int -> Word64
indexWord8ArrayAsWord64 :: BA -> Int -> Word64
indexWord8ArrayAsWord64 (BA# ByteArray#
ba#) (I# Int#
i#) = Word# -> Word64
W64# (ByteArray# -> Int# -> Word#
indexWord8ArrayAsWord64# ByteArray#
ba# Int#
i#)
#endif
newByteArray :: Int -> ST s (MBA s)
newByteArray :: Int -> ST s (MBA s)
newByteArray (I# Int#
len#) =
STRep s (MBA s) -> ST s (MBA s)
forall s a. STRep s a -> ST s a
ST (STRep s (MBA s) -> ST s (MBA s))
-> STRep s (MBA s) -> ST s (MBA s)
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case Int# -> 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 -> MBA s
forall s. MutableByteArray# s -> MBA s
MBA# MutableByteArray# s
mba# #)
unsafeFreezeByteArray :: MBA s -> ST s BA
unsafeFreezeByteArray :: MBA s -> ST s BA
unsafeFreezeByteArray (MBA# MutableByteArray# s
mba#) =
STRep s BA -> ST s BA
forall s a. STRep s a -> ST s a
ST (STRep s BA -> ST s BA) -> STRep s BA -> ST s BA
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case MutableByteArray# 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# -> BA
BA# ByteArray#
ba# #)
writeWord8Array :: MBA s -> Int -> Word8 -> ST s ()
writeWord8Array :: MBA s -> Int -> Word8 -> ST s ()
writeWord8Array (MBA# MutableByteArray# s
mba#) (I# Int#
i#) (W8# Word#
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 -> case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8Array# MutableByteArray# s
mba# Int#
i# Word#
w# State# s
s of
State# s
s -> (# State# s
s, () #)
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
writeWord64Array :: MBA s -> Int -> Word64 -> ST s ()
writeWord64Array :: MBA s -> Int -> Word64 -> ST s ()
writeWord64Array (MBA# MutableByteArray# s
mba#) (I# Int#
i#) (W64# Word#
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 -> case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord64Array# MutableByteArray# s
mba# Int#
i# Word#
w# State# s
s of
State# s
s -> (# State# s
s, () #)
#endif
copyByteArray :: BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray :: BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (BA# ByteArray#
src#) (I# Int#
src_off#) (MBA# MutableByteArray# 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 -> case ByteArray#
-> 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 of
State# s
s -> (# State# s
s, () #)
setByteArray :: MBA s -> Int -> Int -> Int -> ST s ()
setByteArray :: MBA s -> Int -> Int -> Int -> ST s ()
setByteArray (MBA# MutableByteArray# 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 -> case MutableByteArray# 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 of
State# s
s -> (# State# s
s, () #)
copyMutableByteArray :: MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
copyMutableByteArray :: MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
copyMutableByteArray (MBA# MutableByteArray# s
src#) (I# Int#
src_off#) (MBA# MutableByteArray# 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 -> case MutableByteArray# 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 of
State# s
s -> (# State# s
s, () #)
#if MIN_VERSION_base(4,11,0)
compareByteArraysOff :: BA
-> Int
-> BA
-> Int
-> Int
-> Int
compareByteArraysOff :: BA -> Int -> BA -> Int -> Int -> Int
compareByteArraysOff (BA# ByteArray#
ba1#) (I# Int#
ba1off#) (BA# ByteArray#
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#)
#endif
copyByteArray# :: ByteArray# -> Int#
-> MutableByteArray# s -> Int#
-> Int#
-> State# s -> State# s
copyByteArray# :: 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#
#if !MIN_VERSION_bytestring(0,10,10)
packCString :: CString -> IO ShortByteString
packCString cstr = do
len <- BS.c_strlen cstr
packCStringLen (cstr, fromIntegral len)
useAsCString :: ShortByteString -> (CString -> IO a) -> IO a
useAsCString sbs action =
allocaBytes (l+1) $ \buf -> do
copyToPtr sbs 0 buf (fromIntegral l)
pokeByteOff buf l (0::Word8)
action buf
where l = length sbs
useAsCStringLen :: ShortByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen sbs action =
allocaBytes l $ \buf -> do
copyToPtr sbs 0 buf (fromIntegral l)
action (buf, l)
where l = length sbs
packCStringLen :: CStringLen -> IO ShortByteString
packCStringLen (cstr, len) | len >= 0 = createFromPtr cstr len
packCStringLen (_, len) =
moduleErrorIO "packCStringLen" ("negative length: " ++ show len)
moduleErrorIO :: HasCallStack => String -> String -> IO a
moduleErrorIO fun msg = throwIO . userError $ moduleErrorMsg fun msg
{-# NOINLINE moduleErrorIO #-}
#endif
moduleErrorMsg :: String -> String -> String
moduleErrorMsg :: String -> String -> String
moduleErrorMsg String
fun String
msg = String
"System.AbstractFilePath.Data.ByteString.Short." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fun String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
':'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
msg
findFromEndUntil :: (Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil :: (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)
where
ba :: BA
ba = ShortByteString -> BA
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 (BA -> Int -> Word8
indexWord8Array BA
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 -> Int
findIndexOrLength :: (Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength Word8 -> Bool
k ShortByteString
sbs = Int -> Int
go Int
0
where
l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
ba :: BA
ba = ShortByteString -> BA
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 (BA -> Int -> Word8
indexWord8Array BA
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 (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. MBA s -> ST s ()) -> ShortByteString
create Int
len (\MBA s
mba -> MBA s -> Int -> [Word8] -> ST s ()
forall s. MBA s -> Int -> [Word8] -> ST s ()
go MBA s
mba Int
len [Word8]
ws0)
where
go :: MBA s -> Int -> [Word8] -> ST s ()
go :: MBA s -> Int -> [Word8] -> ST s ()
go !MBA s
_ !Int
_ [] = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
go !MBA s
mba !Int
i (Word8
w:[Word8]
ws) = do
MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Word8
w
MBA s -> Int -> [Word8] -> ST s ()
forall s. MBA s -> Int -> [Word8] -> ST s ()
go MBA 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 = case Word8 -> ShortByteString -> Maybe Int
elemIndex Word8
c ShortByteString
sbs of
Maybe Int
Nothing -> (ShortByteString
sbs, ShortByteString
empty)
Just Int
n -> (Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
sbs, Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
sbs)
errorEmptySBS :: HasCallStack => String -> a
errorEmptySBS :: String -> a
errorEmptySBS String
fun = String -> String -> a
forall a. (?callStack::CallStack) => String -> String -> a
moduleError String
fun String
"empty ShortByteString"
{-# NOINLINE errorEmptySBS #-}
moduleError :: HasCallStack => String -> String -> a
moduleError :: String -> String -> a
moduleError String
fun String
msg = String -> a
forall a. (?callStack::CallStack) => String -> a
error (String -> String -> String
moduleErrorMsg String
fun String
msg)
{-# NOINLINE moduleError #-}
#if !MIN_VERSION_bytestring(0,10,9)
checkedAdd :: String -> Int -> Int -> Int
checkedAdd fun x y
| r >= 0 = r
| otherwise = overflowError fun
where r = x + y
{-# INLINE checkedAdd #-}
overflowError :: String -> a
overflowError fun = error $ "Data.ByteString." ++ fun ++ ": size overflow"
#endif
#endif