{-# language BangPatterns #-}
{-# language BlockArguments #-}
{-# language DuplicateRecordFields #-}
{-# language MagicHash #-}
{-# language NamedFieldPuns #-}
{-# language RankNTypes #-}
{-# language TupleSections #-}
{-# language TypeApplications #-}
{-# language UnboxedTuples #-}
module Data.Bytes
(
Bytes
, Pure.empty
, Pure.emptyPinned
, Pure.emptyPinnedU
, null
, Pure.length
, uncons
, unsnoc
, any
, all
, singleton
, doubleton
, tripleton
, replicate
, singletonU
, doubletonU
, tripletonU
, replicateU
, takeWhile
, dropWhile
, takeWhileEnd
, dropWhileEnd
, Pure.foldl
, Pure.foldl'
, Pure.foldr
, Pure.foldr'
, Pure.ifoldl'
, Pure.foldlM
, Pure.foldrM
, elem
, Byte.split
, Byte.splitU
, Byte.splitInit
, Byte.splitInitU
, Byte.splitNonEmpty
, Byte.splitStream
, Byte.split1
, Byte.split2
, Byte.split3
, Byte.split4
, Byte.splitEnd1
, intercalate
, intercalateByte2
, Byte.count
, isPrefixOf
, isSuffixOf
, isInfixOf
, stripPrefix
, stripOptionalPrefix
, stripSuffix
, stripOptionalSuffix
, longestCommonPrefix
, stripCStringPrefix
, isBytePrefixOf
, isByteSuffixOf
, equalsLatin1
, equalsLatin2
, equalsLatin3
, equalsLatin4
, equalsLatin5
, equalsLatin6
, equalsLatin7
, equalsLatin8
, equalsLatin9
, equalsLatin10
, equalsLatin11
, equalsLatin12
, equalsCString
, Pure.fnv1a32
, Pure.fnv1a64
, unsafeTake
, unsafeDrop
, unsafeIndex
, Pure.unsafeCopy
, Pure.pin
, Pure.contents
, touch
, Pure.toByteArray
, Pure.toByteArrayClone
, Pure.toPinnedByteArray
, Pure.toPinnedByteArrayClone
, fromAsciiString
, fromLatinString
, Pure.fromByteArray
, toLatinString
, fromCString#
, Pure.toByteString
, Pure.pinnedToByteString
, Pure.fromByteString
, fromShortByteString
, toShortByteString
, toShortByteStringClone
, toLowerAsciiByteArrayClone
, BIO.hGet
, readFile
, BIO.hPut
, lift
, unlift
) where
import Prelude hiding (length,takeWhile,dropWhile,null,foldl,foldr,elem,replicate,any,all,readFile)
import Control.Monad.Primitive (PrimMonad,primitive_,unsafeIOToPrim)
import Control.Monad.ST.Run (runByteArrayST)
import Cstrlen (cstringLength#)
import Data.Bits((.&.),(.|.),shiftL,finiteBitSize)
import Data.Bytes.Pure (length,fromByteArray,foldr)
import Data.Bytes.Types (Bytes(Bytes,array,offset))
import Data.ByteString.Short.Internal (ShortByteString(SBS))
import Data.Maybe (fromMaybe)
import Data.Primitive (ByteArray(ByteArray))
import Foreign.C.String (CString)
import Foreign.Ptr (Ptr,plusPtr,castPtr)
import GHC.Exts (Addr#,Word#,Int#)
import GHC.Exts (Int(I#),Ptr(Ptr))
import GHC.Word (Word8(W8#),Word32)
import Reps (Bytes#(..),word8ToWord#)
import qualified Data.Bytes.Byte as Byte
import qualified Data.Bytes.Chunks as Chunks
import qualified Data.Bytes.IO as BIO
import qualified Data.Bytes.Pure as Pure
import qualified Data.Bytes.Text.Ascii as Ascii
import qualified Data.Bytes.Text.AsciiExt as AsciiExt
import qualified Data.Bytes.Text.Latin1 as Latin1
import qualified Data.Bytes.Types as Types
import qualified Data.Foldable as F
import qualified Data.List as List
import qualified Data.Primitive as PM
import qualified Data.Primitive.Ptr as PM
import qualified GHC.Exts as Exts
null :: Bytes -> Bool
{-# inline null #-}
null :: Bytes -> Bool
null (Bytes ByteArray
_ Int
_ Int
len) = Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
uncons :: Bytes -> Maybe (Word8, Bytes)
{-# inline uncons #-}
uncons :: Bytes -> Maybe (Word8, Bytes)
uncons Bytes
b = case Bytes -> Int
length Bytes
b of
Int
0 -> Maybe (Word8, Bytes)
forall a. Maybe a
Nothing
Int
_ -> (Word8, Bytes) -> Maybe (Word8, Bytes)
forall a. a -> Maybe a
Just (Bytes -> Int -> Word8
unsafeIndex Bytes
b Int
0, Int -> Bytes -> Bytes
unsafeDrop Int
1 Bytes
b)
unsnoc :: Bytes -> Maybe (Bytes, Word8)
{-# inline unsnoc #-}
unsnoc :: Bytes -> Maybe (Bytes, Word8)
unsnoc b :: Bytes
b@(Bytes ByteArray
arr Int
off Int
len) = case Int
len of
Int
0 -> Maybe (Bytes, Word8)
forall a. Maybe a
Nothing
Int
_ -> let !len' :: Int
len' = Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 in
(Bytes, Word8) -> Maybe (Bytes, Word8)
forall a. a -> Maybe a
Just (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr Int
off Int
len', Bytes -> Int -> Word8
unsafeIndex Bytes
b Int
len')
isBytePrefixOf :: Word8 -> Bytes -> Bool
{-# inline isBytePrefixOf #-}
isBytePrefixOf :: Word8 -> Bytes -> Bool
isBytePrefixOf Word8
w Bytes
b = case Bytes -> Int
length Bytes
b of
Int
0 -> Bool
False
Int
_ -> Bytes -> Int -> Word8
unsafeIndex Bytes
b Int
0 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w
isByteSuffixOf :: Word8 -> Bytes -> Bool
isByteSuffixOf :: Word8 -> Bytes -> Bool
isByteSuffixOf Word8
w Bytes
b = case Int
len of
Int
0 -> Bool
False
Int
_ -> Bytes -> Int -> Word8
unsafeIndex Bytes
b (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w
where
len :: Int
len = Bytes -> Int
length Bytes
b
isPrefixOf :: Bytes -> Bytes -> Bool
isPrefixOf :: Bytes -> Bytes -> Bool
isPrefixOf (Bytes ByteArray
a Int
aOff Int
aLen) (Bytes ByteArray
b Int
bOff Int
bLen) =
if Int
aLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
bLen
then ByteArray -> Int -> ByteArray -> Int -> Int -> Ordering
compareByteArrays ByteArray
a Int
aOff ByteArray
b Int
bOff Int
aLen Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ
else Bool
False
isSuffixOf :: Bytes -> Bytes -> Bool
isSuffixOf :: Bytes -> Bytes -> Bool
isSuffixOf (Bytes ByteArray
a Int
aOff Int
aLen) (Bytes ByteArray
b Int
bOff Int
bLen) =
if Int
aLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
bLen
then ByteArray -> Int -> ByteArray -> Int -> Int -> Ordering
compareByteArrays ByteArray
a Int
aOff ByteArray
b (Int
bOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
bLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
aLen) Int
aLen Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ
else Bool
False
isInfixOf :: Bytes
-> Bytes
-> Bool
isInfixOf :: Bytes -> Bytes -> Bool
isInfixOf Bytes
p Bytes
s = Bytes -> Bool
null Bytes
p Bool -> Bool -> Bool
|| (Bool -> Bool
not (Bool -> Bool) -> (Bytes -> Bool) -> Bytes -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bytes -> Bool
null) ((Bytes, Bytes) -> Bytes
forall a b. (a, b) -> b
snd ((Bytes, Bytes) -> Bytes) -> (Bytes, Bytes) -> Bytes
forall a b. (a -> b) -> a -> b
$ Bytes -> Bytes -> (Bytes, Bytes)
breakSubstring Bytes
p Bytes
s)
breakSubstring :: Bytes
-> Bytes
-> (Bytes,Bytes)
breakSubstring :: Bytes -> Bytes -> (Bytes, Bytes)
breakSubstring Bytes
pat =
case Int
lp of
Int
0 -> (Bytes
forall a. Monoid a => a
mempty,)
Int
1 -> Word8 -> Bytes -> (Bytes, Bytes)
breakByte (Bytes -> Word8
unsafeHead Bytes
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 Bytes -> (Bytes, Bytes)
shift
else Bytes -> (Bytes, Bytes)
karpRabin
where
unsafeSplitAt :: Int -> Bytes -> (Bytes, Bytes)
unsafeSplitAt Int
i Bytes
s = (Int -> Bytes -> Bytes
unsafeTake Int
i Bytes
s, Int -> Bytes -> Bytes
unsafeDrop Int
i Bytes
s)
lp :: Int
lp = Bytes -> Int
length Bytes
pat
{-# INLINE breakByte #-}
breakByte :: Word8 -> Bytes -> (Bytes, Bytes)
breakByte Word8
b Bytes
bytes = (Bytes, Bytes) -> Maybe (Bytes, Bytes) -> (Bytes, Bytes)
forall a. a -> Maybe a -> a
fromMaybe (Bytes
forall a. Monoid a => a
mempty,Bytes
bytes) (Maybe (Bytes, Bytes) -> (Bytes, Bytes))
-> Maybe (Bytes, Bytes) -> (Bytes, Bytes)
forall a b. (a -> b) -> a -> b
$ Word8 -> Bytes -> Maybe (Bytes, Bytes)
Byte.split1 Word8
b Bytes
bytes
{-# INLINE karpRabin #-}
karpRabin :: Bytes -> (Bytes, Bytes)
karpRabin :: Bytes -> (Bytes, Bytes)
karpRabin Bytes
src
| Bytes -> Int
length Bytes
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lp = (Bytes
src,Bytes
forall a. Monoid a => a
mempty)
| Bool
otherwise = Word32 -> Int -> (Bytes, Bytes)
search (Bytes -> Word32
rollingHash (Bytes -> Word32) -> Bytes -> Word32
forall a b. (a -> b) -> a -> b
$ Int -> Bytes -> Bytes
unsafeTake Int
lp Bytes
src) Int
lp
where
k :: Word32
k = Word32
2891336453 :: Word32
rollingHash :: Bytes -> Word32
rollingHash = (Word32 -> Word8 -> Word32) -> Word32 -> Bytes -> Word32
forall a. (a -> Word8 -> a) -> a -> Bytes -> a
Pure.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 = Bytes -> Word32
rollingHash Bytes
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
. Bytes -> Int -> Word8
unsafeIndex Bytes
src
search :: Word32 -> Int -> (Bytes, Bytes)
search !Word32
hs !Int
i
| Word32
hp Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
hs Bool -> Bool -> Bool
&& Bytes
pat Bytes -> Bytes -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Bytes -> Bytes
unsafeTake Int
lp Bytes
b = (Bytes, Bytes)
u
| Bytes -> Int
length Bytes
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i = (Bytes
src,Bytes
forall a. Monoid a => a
mempty)
| Bool
otherwise = Word32 -> Int -> (Bytes, Bytes)
search Word32
hs' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
where
u :: (Bytes, Bytes)
u@(Bytes
_, Bytes
b) = Int -> Bytes -> (Bytes, Bytes)
unsafeSplitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Bytes
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 shift #-}
shift :: Bytes -> (Bytes, Bytes)
shift :: Bytes -> (Bytes, Bytes)
shift !Bytes
src
| Bytes -> Int
length Bytes
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lp = (Bytes
src,Bytes
forall a. Monoid a => a
mempty)
| Bool
otherwise = Word -> Int -> (Bytes, Bytes)
search (Bytes -> Word
intoWord (Bytes -> Word) -> Bytes -> Word
forall a b. (a -> b) -> a -> b
$ Int -> Bytes -> Bytes
unsafeTake Int
lp Bytes
src) Int
lp
where
intoWord :: Bytes -> Word
intoWord :: Bytes -> Word
intoWord = (Word -> Word8 -> Word) -> Word -> Bytes -> Word
forall a. (a -> Word8 -> a) -> a -> Bytes -> a
Pure.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 = Bytes -> Word
intoWord Bytes
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 -> (Bytes, Bytes)
search !Word
w !Int
i
| Word
w Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
wp = Int -> Bytes -> (Bytes, Bytes)
unsafeSplitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Bytes
src
| Bytes -> Int
length Bytes
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i = (Bytes
src, Bytes
forall a. Monoid a => a
mempty)
| Bool
otherwise = Word -> Int -> (Bytes, Bytes)
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 (Bytes -> Int -> Word8
unsafeIndex Bytes
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)
longestCommonPrefix :: Bytes -> Bytes -> Bytes
longestCommonPrefix :: Bytes -> Bytes -> Bytes
longestCommonPrefix Bytes
a Bytes
b = Int -> Bytes
loop Int
0
where
loop :: Int -> Bytes
loop :: Int -> Bytes
loop !Int
into
| Int
into Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
maxLen
Bool -> Bool -> Bool
&& Bytes -> Int -> Word8
unsafeIndex Bytes
a Int
into Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Bytes -> Int -> Word8
unsafeIndex Bytes
b Int
into
= Int -> Bytes
loop (Int
into Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
| Bool
otherwise = Int -> Bytes -> Bytes
unsafeTake Int
into Bytes
a
maxLen :: Int
maxLen = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Bytes -> Int
length Bytes
a) (Bytes -> Int
length Bytes
b)
singleton :: Word8 -> Bytes
{-# inline singleton #-}
singleton :: Word8 -> Bytes
singleton !Word8
a = ByteArray -> Int -> Int -> Bytes
Bytes (Word8 -> ByteArray
singletonU Word8
a) Int
0 Int
1
doubleton :: Word8 -> Word8 -> Bytes
{-# inline doubleton #-}
doubleton :: Word8 -> Word8 -> Bytes
doubleton !Word8
a !Word8
b = ByteArray -> Int -> Int -> Bytes
Bytes (Word8 -> Word8 -> ByteArray
doubletonU Word8
a Word8
b) Int
0 Int
2
tripleton :: Word8 -> Word8 -> Word8 -> Bytes
{-# inline tripleton #-}
tripleton :: Word8 -> Word8 -> Word8 -> Bytes
tripleton !Word8
a !Word8
b !Word8
c = ByteArray -> Int -> Int -> Bytes
Bytes (Word8 -> Word8 -> Word8 -> ByteArray
tripletonU Word8
a Word8
b Word8
c) Int
0 Int
3
singletonU :: Word8 -> ByteArray
{-# inline singletonU #-}
singletonU :: Word8 -> ByteArray
singletonU !Word8
a = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST do
MutableByteArray s
arr <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
1
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
0 Word8
a
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr
doubletonU :: Word8 -> Word8 -> ByteArray
{-# inline doubletonU #-}
doubletonU :: Word8 -> Word8 -> ByteArray
doubletonU !Word8
a !Word8
b = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST do
MutableByteArray s
arr <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
2
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
0 Word8
a
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
1 Word8
b
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr
tripletonU :: Word8 -> Word8 -> Word8 -> ByteArray
{-# inline tripletonU #-}
tripletonU :: Word8 -> Word8 -> Word8 -> ByteArray
tripletonU !Word8
a !Word8
b !Word8
c = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST do
MutableByteArray s
arr <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
3
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
0 Word8
a
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
1 Word8
b
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
2 Word8
c
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr
replicate ::
Int
-> Word8
-> Bytes
replicate :: Int -> Word8 -> Bytes
replicate !Int
n !Word8
w = ByteArray -> Int -> Int -> Bytes
Bytes (Int -> Word8 -> ByteArray
replicateU Int
n Word8
w) Int
0 Int
n
replicateU :: Int -> Word8 -> ByteArray
replicateU :: Int -> Word8 -> ByteArray
replicateU !Int
n !Word8
w = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST do
MutableByteArray s
arr <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
n
MutableByteArray (PrimState (ST s))
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> Int -> a -> m ()
PM.setByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
0 Int
n Word8
w
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr
stripPrefix :: Bytes -> Bytes -> Maybe Bytes
stripPrefix :: Bytes -> Bytes -> Maybe Bytes
stripPrefix !Bytes
pre !Bytes
str = if Bytes
pre Bytes -> Bytes -> Bool
`isPrefixOf` Bytes
str
then Bytes -> Maybe Bytes
forall a. a -> Maybe a
Just (ByteArray -> Int -> Int -> Bytes
Bytes (Bytes -> ByteArray
array Bytes
str) (Bytes -> Int
offset Bytes
str Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
pre) (Bytes -> Int
length Bytes
str Int -> Int -> Int
forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
pre))
else Maybe Bytes
forall a. Maybe a
Nothing
stripOptionalPrefix :: Bytes -> Bytes -> Bytes
stripOptionalPrefix :: Bytes -> Bytes -> Bytes
stripOptionalPrefix !Bytes
pre !Bytes
str = if Bytes
pre Bytes -> Bytes -> Bool
`isPrefixOf` Bytes
str
then ByteArray -> Int -> Int -> Bytes
Bytes (Bytes -> ByteArray
array Bytes
str) (Bytes -> Int
offset Bytes
str Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
pre) (Bytes -> Int
length Bytes
str Int -> Int -> Int
forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
pre)
else Bytes
str
stripSuffix :: Bytes -> Bytes -> Maybe Bytes
stripSuffix :: Bytes -> Bytes -> Maybe Bytes
stripSuffix !Bytes
suf !Bytes
str = if Bytes
suf Bytes -> Bytes -> Bool
`isSuffixOf` Bytes
str
then Bytes -> Maybe Bytes
forall a. a -> Maybe a
Just (ByteArray -> Int -> Int -> Bytes
Bytes (Bytes -> ByteArray
array Bytes
str) (Bytes -> Int
offset Bytes
str) (Bytes -> Int
length Bytes
str Int -> Int -> Int
forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
suf))
else Maybe Bytes
forall a. Maybe a
Nothing
stripOptionalSuffix :: Bytes -> Bytes -> Bytes
stripOptionalSuffix :: Bytes -> Bytes -> Bytes
stripOptionalSuffix !Bytes
suf !Bytes
str = if Bytes
suf Bytes -> Bytes -> Bool
`isSuffixOf` Bytes
str
then ByteArray -> Int -> Int -> Bytes
Bytes (Bytes -> ByteArray
array Bytes
str) (Bytes -> Int
offset Bytes
str) (Bytes -> Int
length Bytes
str Int -> Int -> Int
forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
suf)
else Bytes
str
elem :: Word8 -> Bytes -> Bool
elem :: Word8 -> Bytes -> Bool
elem (W8# Word#
w) Bytes
b = case Int# -> Word# -> Bytes -> Int#
elemLoop Int#
0# (Word# -> Word#
word8ToWord# Word#
w) Bytes
b of
Int#
1# -> Bool
True
Int#
_ -> Bool
False
elemLoop :: Int# -> Word# -> Bytes -> Int#
elemLoop :: Int# -> Word# -> Bytes -> Int#
elemLoop !Int#
r !Word#
w (Bytes arr :: ByteArray
arr@(ByteArray ByteArray#
arr# ) off :: Int
off@(I# Int#
off# ) Int
len) = case Int
len of
Int
0 -> Int#
r
Int
_ -> Int# -> Word# -> Bytes -> Int#
elemLoop (Int# -> Int# -> Int#
Exts.orI# Int#
r (Word# -> Word# -> Int#
Exts.eqWord# Word#
w (Word# -> Word#
word8ToWord# (ByteArray# -> Int# -> Word#
Exts.indexWord8Array# ByteArray#
arr# Int#
off# )) )) Word#
w (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))
takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline takeWhile #-}
takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes
takeWhile Word8 -> Bool
k Bytes
b = Int -> Bytes -> Bytes
unsafeTake ((Word8 -> Bool) -> Bytes -> Int
countWhile Word8 -> Bool
k Bytes
b) Bytes
b
dropWhile :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline dropWhile #-}
dropWhile :: (Word8 -> Bool) -> Bytes -> Bytes
dropWhile Word8 -> Bool
k Bytes
b = Int -> Bytes -> Bytes
unsafeDrop ((Word8 -> Bool) -> Bytes -> Int
countWhile Word8 -> Bool
k Bytes
b) Bytes
b
unsafeIndex :: Bytes -> Int -> Word8
{-# inline unsafeIndex #-}
unsafeIndex :: Bytes -> Int -> Word8
unsafeIndex (Bytes ByteArray
arr Int
off Int
_) Int
ix = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ix)
{-# inline unsafeHead #-}
unsafeHead :: Bytes -> Word8
unsafeHead :: Bytes -> Word8
unsafeHead Bytes
bs = Bytes -> Int -> Word8
unsafeIndex Bytes
bs Int
0
dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline dropWhileEnd #-}
dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
dropWhileEnd Word8 -> Bool
k !Bytes
b = Int -> Bytes -> Bytes
unsafeTake (Bytes -> Int
length Bytes
b Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Word8 -> Bool) -> Bytes -> Int
countWhileEnd Word8 -> Bool
k Bytes
b) Bytes
b
takeWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline takeWhileEnd #-}
takeWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
takeWhileEnd Word8 -> Bool
k !Bytes
b =
let n :: Int
n = (Word8 -> Bool) -> Bytes -> Int
countWhileEnd Word8 -> Bool
k Bytes
b
in ByteArray -> Int -> Int -> Bytes
Bytes (Bytes -> ByteArray
array Bytes
b) (Bytes -> Int
offset Bytes
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
b Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) Int
n
unsafeTake :: Int -> Bytes -> Bytes
{-# inline unsafeTake #-}
unsafeTake :: Int -> Bytes -> Bytes
unsafeTake Int
n (Bytes ByteArray
arr Int
off Int
_) =
ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr Int
off Int
n
unsafeDrop :: Int -> Bytes -> Bytes
{-# inline unsafeDrop #-}
unsafeDrop :: Int -> Bytes -> Bytes
unsafeDrop Int
n (Bytes ByteArray
arr Int
off Int
len) =
ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
countWhile :: (Word8 -> Bool) -> Bytes -> Int
{-# inline countWhile #-}
countWhile :: (Word8 -> Bool) -> Bytes -> Int
countWhile Word8 -> Bool
k (Bytes ByteArray
arr Int
off0 Int
len0) = Int -> Int -> Int -> Int
forall t p. (Ord t, Num t, Num p) => Int -> t -> p -> p
go Int
off0 Int
len0 Int
0 where
go :: Int -> t -> p -> p
go !Int
off !t
len !p
n = if t
len t -> t -> Bool
forall a. Ord a => a -> a -> Bool
> t
0
then if Word8 -> Bool
k (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
then Int -> t -> p -> p
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (t
len t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (p
n p -> p -> p
forall a. Num a => a -> a -> a
+ p
1)
else p
n
else p
n
countWhileEnd :: (Word8 -> Bool) -> Bytes -> Int
{-# inline countWhileEnd #-}
countWhileEnd :: (Word8 -> Bool) -> Bytes -> Int
countWhileEnd Word8 -> Bool
k (Bytes ByteArray
arr Int
off0 Int
len0) = Int -> Int -> Int -> Int
forall t p. (Ord t, Num t, Num p) => Int -> t -> p -> p
go (Int
off0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Int
len0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int
0 where
go :: Int -> t -> p -> p
go !Int
off !t
len !p
n = if t
len t -> t -> Bool
forall a. Ord a => a -> a -> Bool
>= t
0
then if Word8 -> Bool
k (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
then Int -> t -> p -> p
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (t
len t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (p
n p -> p -> p
forall a. Num a => a -> a -> a
+ p
1)
else p
n
else p
n
fromAsciiString :: String -> Bytes
{-# DEPRECATED fromAsciiString "use Data.Bytes.Text.Ascii.fromString instead" #-}
{-# INLINE fromAsciiString #-}
fromAsciiString :: String -> Bytes
fromAsciiString = String -> Bytes
Ascii.fromString
fromLatinString :: String -> Bytes
{-# DEPRECATED fromLatinString "use Data.Bytes.Text.Latin1.fromString instead" #-}
{-# INLINE fromLatinString #-}
fromLatinString :: String -> Bytes
fromLatinString = String -> Bytes
Latin1.fromString
toLatinString :: Bytes -> String
{-# DEPRECATED toLatinString "use Data.Bytes.Text.Latin1.toString instead" #-}
{-# INLINE toLatinString #-}
toLatinString :: Bytes -> String
toLatinString = Bytes -> String
Latin1.toString
fromCString# :: Addr# -> Bytes
fromCString# :: Addr# -> Bytes
fromCString# Addr#
a = ByteArray -> Int -> Int -> Bytes
Bytes
( (forall s. ST s ByteArray) -> ByteArray
runByteArrayST ((forall s. ST s ByteArray) -> ByteArray)
-> (forall s. ST s ByteArray) -> ByteArray
forall a b. (a -> b) -> a -> b
$ do
dst :: MutableByteArray s
dst@(PM.MutableByteArray MutableByteArray# s
dst# ) <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Ptr Word8 -> Int -> ST s ()
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m ()
PM.copyPtrToMutablePrimArray
(MutableByteArray# s -> MutablePrimArray s Word8
forall s a. MutableByteArray# s -> MutablePrimArray s a
PM.MutablePrimArray MutableByteArray# s
dst# ) Int
0 (Addr# -> Ptr Word8
forall a. Addr# -> Ptr a
Ptr Addr#
a :: Ptr Word8) Int
len
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst
) Int
0 Int
len
where
len :: Int
len = Int# -> Int
I# (Addr# -> Int#
cstringLength# Addr#
a)
compareByteArrays :: ByteArray -> Int -> ByteArray -> Int -> Int -> Ordering
{-# INLINE compareByteArrays #-}
compareByteArrays :: ByteArray -> Int -> ByteArray -> Int -> Int -> Ordering
compareByteArrays (ByteArray ByteArray#
ba1#) (I# Int#
off1#) (ByteArray ByteArray#
ba2#) (I# Int#
off2#) (I# Int#
n#) =
Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Int# -> Int
I# (ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
Exts.compareByteArrays# ByteArray#
ba1# Int#
off1# ByteArray#
ba2# Int#
off2# Int#
n#)) Int
0
equalsLatin1 :: Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin1 "use Data.Bytes.Text.Latin1.equals1 instead" #-}
{-# INLINE equalsLatin1 #-}
equalsLatin1 :: Char -> Bytes -> Bool
equalsLatin1 = Char -> Bytes -> Bool
Latin1.equals1
equalsLatin2 :: Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin2 "use Data.Bytes.Text.Latin1.equals2 instead" #-}
{-# INLINE equalsLatin2 #-}
equalsLatin2 :: Char -> Char -> Bytes -> Bool
equalsLatin2 = Char -> Char -> Bytes -> Bool
Latin1.equals2
equalsLatin3 :: Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin3 "use Data.Bytes.Text.Latin1.equals3 instead" #-}
{-# INLINE equalsLatin3 #-}
equalsLatin3 :: Char -> Char -> Char -> Bytes -> Bool
equalsLatin3 = Char -> Char -> Char -> Bytes -> Bool
Latin1.equals3
equalsLatin4 :: Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin4 "use Data.Bytes.Text.Latin1.equals4 instead" #-}
{-# INLINE equalsLatin4 #-}
equalsLatin4 :: Char -> Char -> Char -> Char -> Bytes -> Bool
equalsLatin4 = Char -> Char -> Char -> Char -> Bytes -> Bool
Latin1.equals4
equalsLatin5 :: Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin5 "use Data.Bytes.Text.Latin1.equals5 instead" #-}
{-# INLINE equalsLatin5 #-}
equalsLatin5 :: Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
equalsLatin5 = Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
Latin1.equals5
equalsLatin6 :: Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin6 "use Data.Bytes.Text.Latin1.equals6 instead" #-}
{-# INLINE equalsLatin6 #-}
equalsLatin6 :: Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
equalsLatin6 = Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
Latin1.equals6
equalsLatin7 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin7 "use Data.Bytes.Text.Latin1.equals7 instead" #-}
{-# INLINE equalsLatin7 #-}
equalsLatin7 :: Char
-> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
equalsLatin7 = Char
-> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
Latin1.equals7
equalsLatin8 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin8 "use Data.Bytes.Text.Latin1.equals8 instead" #-}
{-# INLINE equalsLatin8 #-}
equalsLatin8 :: Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
equalsLatin8 = Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
Latin1.equals8
equalsLatin9 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin9 "use Data.Bytes.Text.Latin1.equals9 instead" #-}
{-# INLINE equalsLatin9 #-}
equalsLatin9 :: Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
equalsLatin9 = Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
Latin1.equals9
equalsLatin10 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin10 "use Data.Bytes.Text.Latin1.equals10 instead" #-}
{-# INLINE equalsLatin10 #-}
equalsLatin10 :: Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
equalsLatin10 = Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
Latin1.equals10
equalsLatin11 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin11 "use Data.Bytes.Text.Latin1.equals11 instead" #-}
{-# INLINE equalsLatin11 #-}
equalsLatin11 :: Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
equalsLatin11 = Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
Latin1.equals11
equalsLatin12 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool
{-# DEPRECATED equalsLatin12 "use Data.Bytes.Text.Latin1.equals12 instead" #-}
{-# INLINE equalsLatin12 #-}
equalsLatin12 :: Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
equalsLatin12 = Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Bytes
-> Bool
Latin1.equals12
equalsCString :: CString -> Bytes -> Bool
{-# inline equalsCString #-}
equalsCString :: CString -> Bytes -> Bool
equalsCString !CString
ptr0 (Bytes ByteArray
arr Int
off0 Int
len0) = Ptr Word8 -> Int -> Int -> Bool
forall t. (Eq t, Num t) => Ptr Word8 -> Int -> t -> Bool
go (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
ptr0 :: Ptr Word8) Int
off0 Int
len0 where
go :: Ptr Word8 -> Int -> t -> Bool
go !Ptr Word8
ptr !Int
off !t
len = case t
len of
t
0 -> Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
PM.indexOffPtr Ptr Word8
ptr Int
0 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== (Word8
0 :: Word8)
t
_ -> case Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
PM.indexOffPtr Ptr Word8
ptr Int
0 of
Word8
0 -> Bool
False
Word8
c -> Word8
c Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off Bool -> Bool -> Bool
&& Ptr Word8 -> Int -> t -> Bool
go (Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
1) (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (t
len t -> t -> t
forall a. Num a => a -> a -> a
- t
1)
stripCStringPrefix :: CString -> Bytes -> Maybe Bytes
{-# inline stripCStringPrefix #-}
stripCStringPrefix :: CString -> Bytes -> Maybe Bytes
stripCStringPrefix !CString
ptr0 (Bytes ByteArray
arr Int
off0 Int
len0) = Ptr Word8 -> Int -> Int -> Maybe Bytes
forall b.
(Prim b, Eq b, Num b) =>
Ptr b -> Int -> Int -> Maybe Bytes
go (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
ptr0 :: Ptr Word8) Int
off0 Int
len0 where
go :: Ptr b -> Int -> Int -> Maybe Bytes
go !Ptr b
ptr !Int
off !Int
len = case Ptr b -> Int -> b
forall a. Prim a => Ptr a -> Int -> a
PM.indexOffPtr Ptr b
ptr Int
0 of
b
0 -> Bytes -> Maybe Bytes
forall a. a -> Maybe a
Just (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr Int
off Int
len)
b
c -> case Int
len of
Int
0 -> Maybe Bytes
forall a. Maybe a
Nothing
Int
_ -> case b
c b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== ByteArray -> Int -> b
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off of
Bool
True -> Ptr b -> Int -> Int -> Maybe Bytes
go (Ptr b -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr b
ptr Int
1) (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
Bool
False -> Maybe Bytes
forall a. Maybe a
Nothing
touch :: PrimMonad m => Bytes -> m ()
touch :: Bytes -> m ()
touch (Bytes (ByteArray ByteArray#
arr) Int
_ Int
_) = IO () -> m ()
forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim
((State# (PrimState IO) -> State# (PrimState IO)) -> IO ()
forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (\State# (PrimState IO)
s -> ByteArray# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
Exts.touch# ByteArray#
arr State# RealWorld
State# (PrimState IO)
s))
readFile :: FilePath -> IO Bytes
readFile :: String -> IO Bytes
readFile String
f = Chunks -> Bytes
Chunks.concat (Chunks -> Bytes) -> IO Chunks -> IO Bytes
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Chunks
Chunks.readFile String
f
intercalate ::
Bytes
-> [Bytes]
-> Bytes
intercalate :: Bytes -> [Bytes] -> Bytes
intercalate !Bytes
_ [] = Bytes
forall a. Monoid a => a
mempty
intercalate !Bytes
_ [Bytes
x] = Bytes
x
intercalate (Bytes ByteArray
sarr Int
soff Int
slen) (Bytes ByteArray
arr0 Int
off0 Int
len0 : [Bytes]
bs) = ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
r Int
0 Int
fullLen
where
!fullLen :: Int
fullLen = (Int -> Bytes -> Int) -> Int -> [Bytes] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\Int
acc (Bytes ByteArray
_ Int
_ Int
len) -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen) Int
0 [Bytes]
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len0
r :: ByteArray
r = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST ((forall s. ST s ByteArray) -> ByteArray)
-> (forall s. ST s ByteArray) -> ByteArray
forall a b. (a -> b) -> a -> b
$ do
MutableByteArray s
marr <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
fullLen
MutableByteArray (PrimState (ST s))
-> Int -> ByteArray -> Int -> Int -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
marr Int
0 ByteArray
arr0 Int
off0 Int
len0
!Int
_ <- (Int -> Bytes -> ST s Int) -> Int -> [Bytes] -> ST s Int
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
F.foldlM
(\ !Int
currLen (Bytes ByteArray
arr Int
off Int
len) -> do
MutableByteArray (PrimState (ST s))
-> Int -> ByteArray -> Int -> Int -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
marr Int
currLen ByteArray
sarr Int
soff Int
slen
MutableByteArray (PrimState (ST s))
-> Int -> ByteArray -> Int -> Int -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
marr (Int
currLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen) ByteArray
arr Int
off Int
len
Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
currLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen)
) Int
len0 [Bytes]
bs
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
marr
intercalateByte2 ::
Word8
-> Bytes
-> Bytes
-> Bytes
intercalateByte2 :: Word8 -> Bytes -> Bytes -> Bytes
intercalateByte2 !Word8
sep !Bytes
a !Bytes
b = Bytes :: ByteArray -> Int -> Int -> Bytes
Bytes
{ $sel:array:Bytes :: ByteArray
Types.array = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST ((forall s. ST s ByteArray) -> ByteArray)
-> (forall s. ST s ByteArray) -> ByteArray
forall a b. (a -> b) -> a -> b
$ do
MutableByteArray s
dst <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
MutableByteArray (PrimState (ST s)) -> Int -> Bytes -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
Pure.unsafeCopy MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
0 Bytes
a
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Bytes -> Int
length Bytes
a) Word8
sep
MutableByteArray (PrimState (ST s)) -> Int -> Bytes -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
Pure.unsafeCopy MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Bytes -> Int
length Bytes
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Bytes
b
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst
, $sel:length:Bytes :: Int
Types.length = Int
len
, $sel:offset:Bytes :: Int
Types.offset = Int
0
}
where len :: Int
len = Bytes -> Int
length Bytes
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
any :: (Word8 -> Bool) -> Bytes -> Bool
{-# inline any #-}
any :: (Word8 -> Bool) -> Bytes -> Bool
any Word8 -> Bool
f = (Word8 -> Bool -> Bool) -> Bool -> Bytes -> Bool
forall a. (Word8 -> a -> a) -> a -> Bytes -> a
foldr (\Word8
b Bool
r -> Word8 -> Bool
f Word8
b Bool -> Bool -> Bool
|| Bool
r) Bool
False
all :: (Word8 -> Bool) -> Bytes -> Bool
{-# inline all #-}
all :: (Word8 -> Bool) -> Bytes -> Bool
all Word8 -> Bool
f = (Word8 -> Bool -> Bool) -> Bool -> Bytes -> Bool
forall a. (Word8 -> a -> a) -> a -> Bytes -> a
foldr (\Word8
b Bool
r -> Word8 -> Bool
f Word8
b Bool -> Bool -> Bool
&& Bool
r) Bool
True
toShortByteString :: Bytes -> ShortByteString
{-# inline toShortByteString #-}
toShortByteString :: Bytes -> ShortByteString
toShortByteString !Bytes
b = case Bytes -> ByteArray
Pure.toByteArray Bytes
b of
PM.ByteArray ByteArray#
x -> ByteArray# -> ShortByteString
SBS ByteArray#
x
toShortByteStringClone :: Bytes -> ShortByteString
{-# inline toShortByteStringClone #-}
toShortByteStringClone :: Bytes -> ShortByteString
toShortByteStringClone !Bytes
b = case Bytes -> ByteArray
Pure.toByteArrayClone Bytes
b of
PM.ByteArray ByteArray#
x -> ByteArray# -> ShortByteString
SBS ByteArray#
x
fromShortByteString :: ShortByteString -> Bytes
{-# inline fromShortByteString #-}
fromShortByteString :: ShortByteString -> Bytes
fromShortByteString (SBS ByteArray#
x) = ByteArray -> Bytes
fromByteArray (ByteArray# -> ByteArray
ByteArray ByteArray#
x)
toLowerAsciiByteArrayClone :: Bytes -> ByteArray
{-# DEPRECATED toLowerAsciiByteArrayClone "use Data.Bytes/Text/AsciiExt.toLowerU" #-}
{-# INLINE toLowerAsciiByteArrayClone #-}
toLowerAsciiByteArrayClone :: Bytes -> ByteArray
toLowerAsciiByteArrayClone = Bytes -> ByteArray
AsciiExt.toLowerU
lift :: Bytes# -> Bytes
{-# inline lift #-}
lift :: Bytes# -> Bytes
lift (Bytes# (# ByteArray#
arr, Int#
off, Int#
len #)) = ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int# -> Int
I# Int#
off) (Int# -> Int
I# Int#
len)
unlift :: Bytes -> Bytes#
{-# inline unlift #-}
unlift :: Bytes -> Bytes#
unlift (Bytes (ByteArray ByteArray#
arr) (I# Int#
off) (I# Int#
len)) =
(# ByteArray#, Int#, Int# #) -> Bytes#
Bytes# (# ByteArray#
arr, Int#
off, Int#
len #)