{-# language BangPatterns #-}
{-# language BlockArguments #-}
{-# language DataKinds #-}
{-# language DuplicateRecordFields #-}
{-# language KindSignatures #-}
{-# language MagicHash #-}
{-# language NamedFieldPuns #-}
{-# language RankNTypes #-}
{-# language TupleSections #-}
{-# language TypeApplications #-}
{-# language UnboxedTuples #-}
module Data.Bytes
(
Bytes
, Pure.empty
, Pure.emptyPinned
, Pure.emptyPinnedU
, Pure.null
, Pure.length
, uncons
, unsnoc
, any
, all
, singleton
, doubleton
, tripleton
, replicate
, singletonU
, doubletonU
, tripletonU
, replicateU
, takeWhile
, dropWhile
, takeWhileEnd
, dropWhileEnd
, Pure.map
, Pure.mapU
, 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
, splitTetragram1
, Byte.split2
, Byte.split3
, Byte.split4
, Byte.splitEnd1
, intercalate
, intercalateByte2
, concatArray
, concatArrayU
, replace
, findIndices
, findTetragramIndex
, 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
, Pure.unsafeTake
, Pure.unsafeDrop
, Pure.unsafeIndex
, Pure.unsafeHead
, Pure.unsafeCopy
, Pure.pin
, Pure.contents
, touch
, Pure.toByteArray
, Pure.toByteArrayClone
, Pure.toPinnedByteArray
, Pure.toPinnedByteArrayClone
, fromAsciiString
, fromLatinString
, Pure.fromByteArray
, Pure.fromPrimArray
, toLatinString
, fromCString#
, Pure.toByteString
, Pure.pinnedToByteString
, Pure.fromByteString
, fromShortByteString
, fromShortText
, toShortByteString
, toShortByteStringClone
, toLowerAsciiByteArrayClone
, BIO.hGet
, readFile
, BIO.hPut
, lift
, unlift
, withLength
, withLengthU
) where
import Prelude hiding (length,takeWhile,dropWhile,null,foldl,foldr,elem,replicate,any,all,readFile,map)
import Control.Monad.Primitive (PrimMonad,primitive_,unsafeIOToPrim)
import Control.Monad.ST.Run (runByteArrayST)
import Cstrlen (cstringLength#)
import Data.Bits (unsafeShiftL,(.|.))
import Data.ByteString.Short.Internal (ShortByteString(SBS))
import Data.Bytes.Pure (length,fromByteArray,foldr,unsafeDrop)
import Data.Bytes.Pure (unsafeIndex,toShortByteString)
import Data.Bytes.Types (Bytes(Bytes,array,offset),BytesN(BytesN))
import Data.Bytes.Types (ByteArrayN(ByteArrayN))
import Data.Primitive (Array,ByteArray(ByteArray))
import Data.Text.Short (ShortText)
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 Data.Bytes.Search (findIndices,replace,isInfixOf)
import qualified Arithmetic.Nat as Nat
import qualified Arithmetic.Types as Arithmetic
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 Data.Text.Short as TS
import qualified GHC.Exts as Exts
import qualified GHC.TypeNats as GHC
uncons :: Bytes -> Maybe (Word8, Bytes)
{-# inline uncons #-}
uncons :: Bytes -> Maybe (Word8, Bytes)
uncons Bytes
b = case Bytes -> Int
length Bytes
b of
Int
0 -> forall a. Maybe a
Nothing
Int
_ -> 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 -> forall a. Maybe a
Nothing
Int
_ -> let !len' :: Int
len' = Int
len forall a. Num a => a -> a -> a
- Int
1 in
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 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 forall a. Num a => a -> a -> a
- Int
1) 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 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 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 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 forall a. Num a => a -> a -> a
+ Int
bLen forall a. Num a => a -> a -> a
- Int
aLen) Int
aLen forall a. Eq a => a -> a -> Bool
== Ordering
EQ
else Bool
False
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 forall a. Ord a => a -> a -> Bool
< Int
maxLen
Bool -> Bool -> Bool
&& Bytes -> Int -> Word8
unsafeIndex Bytes
a Int
into forall a. Eq a => a -> a -> Bool
== Bytes -> Int -> Word8
unsafeIndex Bytes
b Int
into
= Int -> Bytes
loop (Int
into forall a. Num a => a -> a -> a
+ Int
1)
| Bool
otherwise = Int -> Bytes -> Bytes
Pure.unsafeTake Int
into Bytes
a
maxLen :: Int
maxLen = 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 <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
1
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
arr Int
0 Word8
a
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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 <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
2
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
arr Int
0 Word8
a
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
arr Int
1 Word8
b
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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 <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
3
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
arr Int
0 Word8
a
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
arr Int
1 Word8
b
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
arr Int
2 Word8
c
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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 <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
n
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> Int -> a -> m ()
PM.setByteArray MutableByteArray s
arr Int
0 Int
n Word8
w
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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 forall a. a -> Maybe a
Just (ByteArray -> Int -> Int -> Bytes
Bytes (Bytes -> ByteArray
array Bytes
str) (Bytes -> Int
offset Bytes
str forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
pre) (Bytes -> Int
length Bytes
str forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
pre))
else 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 forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
pre) (Bytes -> Int
length Bytes
str 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 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 forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
suf))
else 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 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# Word8#
w) Bytes
b = case Int# -> Word# -> Bytes -> Int#
elemLoop Int#
0# (Word8# -> Word#
word8ToWord# Word8#
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 (Word8# -> Word#
word8ToWord# (ByteArray# -> Int# -> Word8#
Exts.indexWord8Array# ByteArray#
arr# Int#
off# )) )) Word#
w (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr (Int
off forall a. Num a => a -> a -> a
+ Int
1) (Int
len 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
Pure.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
Pure.unsafeDrop ((Word8 -> Bool) -> Bytes -> Int
countWhile Word8 -> Bool
k Bytes
b) Bytes
b
dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline dropWhileEnd #-}
dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
dropWhileEnd Word8 -> Bool
k !Bytes
b = Int -> Bytes -> Bytes
Pure.unsafeTake (Bytes -> Int
length Bytes
b 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 forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
b forall a. Num a => a -> a -> a
- Int
n) 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) = forall {t} {t}. (Ord t, Num t, Num t) => Int -> t -> t -> t
go Int
off0 Int
len0 Int
0 where
go :: Int -> t -> t -> t
go !Int
off !t
len !t
n = if t
len forall a. Ord a => a -> a -> Bool
> t
0
then if Word8 -> Bool
k (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
then Int -> t -> t -> t
go (Int
off forall a. Num a => a -> a -> a
+ Int
1) (t
len forall a. Num a => a -> a -> a
- t
1) (t
n forall a. Num a => a -> a -> a
+ t
1)
else t
n
else t
n
countWhileEnd :: (Word8 -> Bool) -> Bytes -> Int
{-# inline countWhileEnd #-}
countWhileEnd :: (Word8 -> Bool) -> Bytes -> Int
countWhileEnd Word8 -> Bool
k (Bytes ByteArray
arr Int
off0 Int
len0) = forall {t} {t}. (Ord t, Num t, Num t) => Int -> t -> t -> t
go (Int
off0 forall a. Num a => a -> a -> a
+ Int
len0 forall a. Num a => a -> a -> a
- Int
1) (Int
len0 forall a. Num a => a -> a -> a
- Int
1) Int
0 where
go :: Int -> t -> t -> t
go !Int
off !t
len !t
n = if t
len forall a. Ord a => a -> a -> Bool
>= t
0
then if Word8 -> Bool
k (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
then Int -> t -> t -> t
go (Int
off forall a. Num a => a -> a -> a
- Int
1) (t
len forall a. Num a => a -> a -> a
- t
1) (t
n forall a. Num a => a -> a -> a
+ t
1)
else t
n
else t
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 a b. (a -> b) -> a -> b
$ do
dst :: MutableByteArray s
dst@(PM.MutableByteArray MutableByteArray# s
dst# ) <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m ()
PM.copyPtrToMutablePrimArray
(forall s a. MutableByteArray# s -> MutablePrimArray s a
PM.MutablePrimArray MutableByteArray# s
dst# ) Int
0 (forall a. Addr# -> Ptr a
Ptr Addr#
a :: Ptr Word8) Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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#) =
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) = forall {t}. (Eq t, Num t) => Ptr Word8 -> Int -> t -> Bool
go (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 -> forall a. Prim a => Ptr a -> Int -> a
PM.indexOffPtr Ptr Word8
ptr Int
0 forall a. Eq a => a -> a -> Bool
== (Word8
0 :: Word8)
t
_ -> case forall a. Prim a => Ptr a -> Int -> a
PM.indexOffPtr Ptr Word8
ptr Int
0 of
Word8
0 -> Bool
False
Word8
c -> Word8
c forall a. Eq a => a -> a -> Bool
== forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off Bool -> Bool -> Bool
&& Ptr Word8 -> Int -> t -> Bool
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
1) (Int
off forall a. Num a => a -> a -> a
+ Int
1) (t
len 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) = forall {b}.
(Prim b, Eq b, Num b) =>
Ptr b -> Int -> Int -> Maybe Bytes
go (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 forall a. Prim a => Ptr a -> Int -> a
PM.indexOffPtr Ptr b
ptr Int
0 of
b
0 -> 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 -> forall a. Maybe a
Nothing
Int
_ -> case b
c forall a. Eq a => a -> a -> Bool
== forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off of
Bool
True -> Ptr b -> Int -> Int -> Maybe Bytes
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr b
ptr Int
1) (Int
off forall a. Num a => a -> a -> a
+ Int
1) (Int
len forall a. Num a => a -> a -> a
- Int
1)
Bool
False -> forall a. Maybe a
Nothing
touch :: PrimMonad m => Bytes -> m ()
touch :: forall (m :: * -> *). PrimMonad m => Bytes -> m ()
touch (Bytes (ByteArray ByteArray#
arr) Int
_ Int
_) = forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim
(forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (\State# (PrimState IO)
s -> touch# :: forall a. a -> State# RealWorld -> State# RealWorld
Exts.touch# ByteArray#
arr State# (PrimState IO)
s))
readFile :: FilePath -> IO Bytes
readFile :: String -> IO Bytes
readFile String
f = Chunks -> Bytes
Chunks.concat 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
_ [] = 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 = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\Int
acc (Bytes ByteArray
_ Int
_ Int
len) -> Int
acc forall a. Num a => a -> a -> a
+ Int
len forall a. Num a => a -> a -> a
+ Int
slen) Int
0 [Bytes]
bs forall a. Num a => a -> a -> a
+ Int
len0
r :: ByteArray
r = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST forall a b. (a -> b) -> a -> b
$ do
MutableByteArray s
marr <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
fullLen
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
marr Int
0 ByteArray
arr0 Int
off0 Int
len0
!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
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
marr Int
currLen ByteArray
sarr Int
soff Int
slen
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
marr (Int
currLen forall a. Num a => a -> a -> a
+ Int
slen) ByteArray
arr Int
off Int
len
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
currLen forall a. Num a => a -> a -> a
+ Int
len forall a. Num a => a -> a -> a
+ Int
slen)
) Int
len0 [Bytes]
bs
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
marr
intercalateByte2 ::
Word8
-> Bytes
-> Bytes
-> Bytes
intercalateByte2 :: Word8 -> Bytes -> Bytes -> Bytes
intercalateByte2 !Word8
sep !Bytes
a !Bytes
b = Bytes
{ $sel:array:Bytes :: ByteArray
Types.array = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST forall a b. (a -> b) -> a -> b
$ do
MutableByteArray s
dst <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
Pure.unsafeCopy MutableByteArray s
dst Int
0 Bytes
a
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
dst (Bytes -> Int
length Bytes
a) Word8
sep
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
Pure.unsafeCopy MutableByteArray s
dst (Bytes -> Int
length Bytes
a forall a. Num a => a -> a -> a
+ Int
1) Bytes
b
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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 forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
b 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 = 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 = 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
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)
fromShortText :: ShortText -> Bytes
{-# inline fromShortText #-}
fromShortText :: ShortText -> Bytes
fromShortText ShortText
t = case ShortText -> ShortByteString
TS.toShortByteString ShortText
t of
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 #)
concatArrayU :: Array Bytes -> ByteArray
{-# noinline concatArrayU #-}
concatArrayU :: Array Bytes -> ByteArray
concatArrayU !Array Bytes
xs = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST forall a b. (a -> b) -> a -> b
$ do
let !arrLen :: Int
arrLen = forall a. Array a -> Int
PM.sizeofArray Array Bytes
xs
let !totalByteLen :: Int
totalByteLen = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (\Int
acc Bytes
b -> Bytes -> Int
length Bytes
b forall a. Num a => a -> a -> a
+ Int
acc) Int
0 Array Bytes
xs
MutableByteArray (PrimState (ST s))
dst <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
totalByteLen
let go :: Int -> Int -> ST s ByteArray
go !Int
ix !Int
dstOff = if Int
ix forall a. Ord a => a -> a -> Bool
< Int
arrLen
then do
Bytes
x <- forall (m :: * -> *) a. Monad m => Array a -> Int -> m a
PM.indexArrayM Array Bytes
xs Int
ix
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
Pure.unsafeCopy MutableByteArray (PrimState (ST s))
dst Int
dstOff Bytes
x
Int -> Int -> ST s ByteArray
go (Int
ix forall a. Num a => a -> a -> a
+ Int
1) (Int
dstOff forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
x)
else forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray (PrimState (ST s))
dst
Int -> Int -> ST s ByteArray
go Int
0 Int
0
concatArray :: Array Bytes -> Bytes
{-# inline concatArray #-}
concatArray :: Array Bytes -> Bytes
concatArray !Array Bytes
xs = ByteArray -> Bytes
Pure.fromByteArray (Array Bytes -> ByteArray
concatArrayU Array Bytes
xs)
withLength ::
Bytes
-> (forall (n :: GHC.Nat). Arithmetic.Nat n -> BytesN n -> a)
-> a
{-# inline withLength #-}
withLength :: forall a. Bytes -> (forall (n :: Nat). Nat n -> BytesN n -> a) -> a
withLength Bytes{ByteArray
array :: ByteArray
$sel:array:Bytes :: Bytes -> ByteArray
array,Int
offset :: Int
$sel:offset:Bytes :: Bytes -> Int
offset,$sel:length:Bytes :: Bytes -> Int
length=Int
len} forall (n :: Nat). Nat n -> BytesN n -> a
f = forall a. Int -> (forall (n :: Nat). Nat n -> a) -> a
Nat.with
Int
len
(\Nat n
n -> forall (n :: Nat). Nat n -> BytesN n -> a
f Nat n
n BytesN{ByteArray
$sel:array:BytesN :: ByteArray
array :: ByteArray
array,Int
$sel:offset:BytesN :: Int
offset :: Int
offset})
withLengthU ::
ByteArray
-> (forall (n :: GHC.Nat). Arithmetic.Nat n -> ByteArrayN n -> a)
-> a
{-# inline withLengthU #-}
withLengthU :: forall a.
ByteArray -> (forall (n :: Nat). Nat n -> ByteArrayN n -> a) -> a
withLengthU !ByteArray
arr forall (n :: Nat). Nat n -> ByteArrayN n -> a
f = forall a. Int -> (forall (n :: Nat). Nat n -> a) -> a
Nat.with
(ByteArray -> Int
PM.sizeofByteArray ByteArray
arr)
(\Nat n
n -> forall (n :: Nat). Nat n -> ByteArrayN n -> a
f Nat n
n (forall (n :: Nat). ByteArray -> ByteArrayN n
ByteArrayN ByteArray
arr))
findTetragramIndex ::
Word8
-> Word8
-> Word8
-> Word8
-> Bytes
-> Maybe Int
findTetragramIndex :: Word8 -> Word8 -> Word8 -> Word8 -> Bytes -> Maybe Int
findTetragramIndex !Word8
w0 !Word8
w1 !Word8
w2 !Word8
w3 (Bytes ByteArray
arr Int
off Int
len) = if Int
len forall a. Ord a => a -> a -> Bool
< Int
4
then forall a. Maybe a
Nothing
else
let !target :: Word32
target =
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w0 :: Word32) Int
24
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w1 :: Word32) Int
16
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w2 :: Word32) Int
8
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w3 :: Word32) Int
0
!end :: Int
end = Int
off forall a. Num a => a -> a -> a
+ Int
len
go :: Int -> Word32 -> Maybe Int
go !Int
ix !Word32
acc = if Word32
acc forall a. Eq a => a -> a -> Bool
== Word32
target
then
let n :: Int
n = Int
ix forall a. Num a => a -> a -> a
- Int
off
in forall a. a -> Maybe a
Just (Int
n forall a. Num a => a -> a -> a
- Int
4)
else if Int
ix forall a. Ord a => a -> a -> Bool
< Int
end
then
let !w :: Word8
w = forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
ix :: Word8
acc' :: Word32
acc' =
(forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w :: Word32)
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL Word32
acc Int
8
in Int -> Word32 -> Maybe Int
go (Int
ix forall a. Num a => a -> a -> a
+ Int
1) Word32
acc'
else forall a. Maybe a
Nothing
!acc0 :: Word32
acc0 =
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
0 :: Word8) :: Word32) Int
24
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
1 :: Word8) :: Word32) Int
16
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
2 :: Word8) :: Word32) Int
8
forall a. Bits a => a -> a -> a
.|.
forall a. Bits a => a -> Int -> a
unsafeShiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
3 :: Word8) :: Word32) Int
0
in Int -> Word32 -> Maybe Int
go Int
4 Word32
acc0
splitTetragram1 ::
Word8
-> Word8
-> Word8
-> Word8
-> Bytes
-> Maybe (Bytes,Bytes)
splitTetragram1 :: Word8 -> Word8 -> Word8 -> Word8 -> Bytes -> Maybe (Bytes, Bytes)
splitTetragram1 !Word8
w0 !Word8
w1 !Word8
w2 !Word8
w3 !Bytes
b = case Word8 -> Word8 -> Word8 -> Word8 -> Bytes -> Maybe Int
findTetragramIndex Word8
w0 Word8
w1 Word8
w2 Word8
w3 Bytes
b of
Maybe Int
Nothing -> forall a. Maybe a
Nothing
Just Int
n -> forall a. a -> Maybe a
Just (Int -> Bytes -> Bytes
Pure.unsafeTake Int
n Bytes
b, Int -> Bytes -> Bytes
Pure.unsafeDrop (Int
n forall a. Num a => a -> a -> a
+ Int
4) Bytes
b)