{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeApplications #-}
module Data.Bytes.Pure
( empty
, emptyPinned
, emptyPinnedU
, pin
, contents
, unsafeCopy
, toByteArray
, toByteArrayClone
, toPinnedByteArray
, toPinnedByteArrayClone
, fromByteArray
, fromPrimArray
, length
, foldlM
, foldrM
, foldl
, foldl'
, foldr
, ifoldl'
, foldr'
, fnv1a32
, fnv1a64
, toByteString
, pinnedToByteString
, fromByteString
, fromLazyByteString
, unsafeDrop
, unsafeTake
, unsafeIndex
, unsafeHead
, map
, mapU
, null
, toShortByteString
, replicate
, replicateU
, splitTetragram1
, findTetragramIndex
, countWhile
, countWhileEnd
, any
, all
) where
import Prelude hiding (Foldable (..), map, replicate, any, all)
import Control.Monad.Primitive (PrimMonad, PrimState)
import Control.Monad.ST.Run (runByteArrayST)
import Data.Bits (unsafeShiftL, (.|.))
import Data.Bits (xor)
import Data.ByteString (ByteString)
import Data.ByteString.Short.Internal (ShortByteString (SBS))
import Data.Bytes.Types (Bytes (Bytes))
import Data.Primitive (ByteArray (ByteArray), MutableByteArray, PrimArray (PrimArray))
import Data.Word (Word32, Word64, Word8)
import Foreign.Ptr (Ptr, plusPtr)
import GHC.IO (unsafeIOToST)
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Internal as ByteString
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Lazy.Internal as LBS
import qualified Data.ByteString.Unsafe as ByteString
import qualified Data.Primitive as PM
import qualified GHC.Exts as Exts
import qualified GHC.ForeignPtr as ForeignPtr
empty :: Bytes
empty :: Bytes
empty = ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
forall a. Monoid a => a
mempty Int
0 Int
0
emptyPinned :: Bytes
emptyPinned :: Bytes
emptyPinned =
ByteArray -> Int -> Int -> Bytes
Bytes
( (forall s. ST s ByteArray) -> ByteArray
runByteArrayST
(Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
0 ST s (MutableByteArray s)
-> (MutableByteArray s -> ST s ByteArray) -> ST s ByteArray
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MutableByteArray s -> ST s ByteArray
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray)
)
Int
0
Int
0
emptyPinnedU :: ByteArray
emptyPinnedU :: ByteArray
emptyPinnedU =
(forall s. ST s ByteArray) -> ByteArray
runByteArrayST
(Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
0 ST s (MutableByteArray s)
-> (MutableByteArray s -> ST s ByteArray) -> ST s ByteArray
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MutableByteArray s -> ST s ByteArray
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray)
pin :: Bytes -> Bytes
pin :: Bytes -> Bytes
pin b :: Bytes
b@(Bytes ByteArray
arr Int
_ Int
len) = case ByteArray -> Bool
PM.isByteArrayPinned ByteArray
arr of
Bool
True -> Bytes
b
Bool
False ->
ByteArray -> Int -> Int -> Bytes
Bytes
( (forall s. ST s ByteArray) -> ByteArray
runByteArrayST do
MutableByteArray s
dst <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
len
MutableByteArray (PrimState (ST s)) -> Int -> Bytes -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
unsafeCopy MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
0 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
)
Int
0
Int
len
toByteArray :: Bytes -> ByteArray
{-# INLINE toByteArray #-}
toByteArray :: Bytes -> ByteArray
toByteArray b :: Bytes
b@(Bytes ByteArray
arr Int
off Int
len)
| Int
off Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0, ByteArray -> Int
PM.sizeofByteArray ByteArray
arr Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len = ByteArray
arr
| Bool
otherwise = Bytes -> ByteArray
toByteArrayClone Bytes
b
toByteArrayClone :: Bytes -> ByteArray
{-# INLINE toByteArrayClone #-}
toByteArrayClone :: Bytes -> ByteArray
toByteArrayClone (Bytes ByteArray
arr Int
off Int
len) = (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
m <- 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 -> 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))
m Int
0 ByteArray
arr Int
off 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))
m
unsafeCopy ::
(PrimMonad m) =>
MutableByteArray (PrimState m) ->
Int ->
Bytes ->
m ()
{-# INLINE unsafeCopy #-}
unsafeCopy :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
unsafeCopy MutableByteArray (PrimState m)
dst Int
dstIx (Bytes ByteArray
src Int
srcIx Int
len) =
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray (PrimState m)
dst Int
dstIx ByteArray
src Int
srcIx Int
len
fromByteArray :: ByteArray -> Bytes
{-# INLINE fromByteArray #-}
fromByteArray :: ByteArray -> Bytes
fromByteArray ByteArray
b = ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
b Int
0 (ByteArray -> Int
PM.sizeofByteArray ByteArray
b)
fromPrimArray :: PrimArray Word8 -> Bytes
{-# INLINE fromPrimArray #-}
fromPrimArray :: PrimArray Word8 -> Bytes
fromPrimArray p :: PrimArray Word8
p@(PrimArray ByteArray#
b) = ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
b) Int
0 (PrimArray Word8 -> Int
forall a. Prim a => PrimArray a -> Int
PM.sizeofPrimArray PrimArray Word8
p)
length :: Bytes -> Int
{-# INLINE length #-}
length :: Bytes -> Int
length (Bytes ByteArray
_ Int
_ Int
len) = Int
len
fnv1a32 :: Bytes -> Word32
fnv1a32 :: Bytes -> Word32
fnv1a32 !Bytes
b =
(Word32 -> Word8 -> Word32) -> Word32 -> Bytes -> Word32
forall a. (a -> Word8 -> a) -> a -> Bytes -> a
foldl'
( \Word32
acc Word8
w -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word32 Word8
w Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
`xor` Word32
acc) Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Word32
0x01000193
)
Word32
0x811c9dc5
Bytes
b
fnv1a64 :: Bytes -> Word64
fnv1a64 :: Bytes -> Word64
fnv1a64 !Bytes
b =
(Word64 -> Word8 -> Word64) -> Word64 -> Bytes -> Word64
forall a. (a -> Word8 -> a) -> a -> Bytes -> a
foldl'
( \Word64
acc Word8
w -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word64 Word8
w Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
`xor` Word64
acc) Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
0x00000100000001B3
)
Word64
0xcbf29ce484222325
Bytes
b
foldl :: (a -> Word8 -> a) -> a -> Bytes -> a
{-# INLINE foldl #-}
foldl :: forall a. (a -> Word8 -> a) -> a -> Bytes -> a
foldl a -> Word8 -> a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) =
Int -> Int -> a
forall {t}. (Eq t, Num t) => Int -> t -> a
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)
where
go :: Int -> t -> a
go !Int
off !t
ix = case t
ix of
(-1) -> a
a0
t
_ -> a -> Word8 -> a
f (Int -> t -> a
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (t
ix t -> t -> t
forall a. Num a => a -> a -> a
- t
1)) (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
foldl' :: (a -> Word8 -> a) -> a -> Bytes -> a
{-# INLINE foldl' #-}
foldl' :: forall a. (a -> Word8 -> a) -> a -> Bytes -> a
foldl' a -> Word8 -> a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) = a -> Int -> Int -> a
forall {t}. (Eq t, Num t) => a -> Int -> t -> a
go a
a0 Int
off0 Int
len0
where
go :: a -> Int -> t -> a
go !a
a !Int
off !t
len = case t
len of
t
0 -> a
a
t
_ -> a -> Int -> t -> a
go (a -> Word8 -> a
f a
a (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)) (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)
foldlM :: (Monad m) => (a -> Word8 -> m a) -> a -> Bytes -> m a
{-# INLINE foldlM #-}
foldlM :: forall (m :: * -> *) a.
Monad m =>
(a -> Word8 -> m a) -> a -> Bytes -> m a
foldlM a -> Word8 -> m a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) = a -> Int -> Int -> m a
forall {t}. (Eq t, Num t) => a -> Int -> t -> m a
go a
a0 Int
off0 Int
len0
where
go :: a -> Int -> t -> m a
go a
a !Int
off !t
len = case t
len of
t
0 -> a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
t
_ -> do
a
a' <- a -> Word8 -> m a
f a
a (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
a -> Int -> t -> m a
go a
a' (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)
foldr :: (Word8 -> a -> a) -> a -> Bytes -> a
{-# INLINE foldr #-}
foldr :: forall a. (Word8 -> a -> a) -> a -> Bytes -> a
foldr Word8 -> a -> a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) = Int -> Int -> a
forall {t}. (Eq t, Num t) => Int -> t -> a
go Int
off0 Int
len0
where
go :: Int -> t -> a
go !Int
off !t
len = case t
len of
t
0 -> a
a0
t
_ -> Word8 -> a -> a
f (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off) (Int -> t -> a
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))
ifoldl' :: (a -> Int -> Word8 -> a) -> a -> Bytes -> a
{-# INLINE ifoldl' #-}
ifoldl' :: forall a. (a -> Int -> Word8 -> a) -> a -> Bytes -> a
ifoldl' a -> Int -> Word8 -> a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) = a -> Int -> Int -> Int -> a
forall {t}. (Eq t, Num t) => a -> Int -> Int -> t -> a
go a
a0 Int
0 Int
off0 Int
len0
where
go :: a -> Int -> Int -> t -> a
go !a
a !Int
ix !Int
off !t
len = case t
len of
t
0 -> a
a
t
_ -> a -> Int -> Int -> t -> a
go (a -> Int -> Word8 -> a
f a
a Int
ix (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)) (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (t
len t -> t -> t
forall a. Num a => a -> a -> a
- t
1)
foldr' :: (Word8 -> a -> a) -> a -> Bytes -> a
{-# INLINE foldr' #-}
foldr' :: forall a. (Word8 -> a -> a) -> a -> Bytes -> a
foldr' Word8 -> a -> a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) =
a -> Int -> Int -> a
forall {t}. (Eq t, Num t) => a -> Int -> t -> a
go a
a0 (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)
where
go :: a -> Int -> t -> a
go !a
a !Int
off !t
ix = case t
ix of
(-1) -> a
a
t
_ -> a -> Int -> t -> a
go (Word8 -> a -> a
f (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off) a
a) (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (t
ix t -> t -> t
forall a. Num a => a -> a -> a
- t
1)
foldrM :: (Monad m) => (Word8 -> a -> m a) -> a -> Bytes -> m a
{-# INLINE foldrM #-}
foldrM :: forall (m :: * -> *) a.
Monad m =>
(Word8 -> a -> m a) -> a -> Bytes -> m a
foldrM Word8 -> a -> m a
f a
a0 (Bytes ByteArray
arr Int
off0 Int
len0) =
a -> Int -> Int -> m a
forall {t}. (Eq t, Num t) => a -> Int -> t -> m a
go a
a0 (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)
where
go :: a -> Int -> t -> m a
go !a
a !Int
off !t
ix = case t
ix of
(-1) -> a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
t
_ -> do
a
a' <- Word8 -> a -> m a
f (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off) a
a
a -> Int -> t -> m a
go a
a' (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (t
ix t -> t -> t
forall a. Num a => a -> a -> a
- t
1)
contents :: Bytes -> Ptr Word8
{-# INLINE contents #-}
contents :: Bytes -> Ptr Word8
contents (Bytes ByteArray
arr Int
off Int
_) = Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr (ByteArray -> Ptr Word8
PM.byteArrayContents ByteArray
arr) Int
off
toPinnedByteArray :: Bytes -> ByteArray
{-# INLINE toPinnedByteArray #-}
toPinnedByteArray :: Bytes -> ByteArray
toPinnedByteArray b :: Bytes
b@(Bytes ByteArray
arr Int
off Int
len)
| Int
off Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0, ByteArray -> Int
PM.sizeofByteArray ByteArray
arr Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len, ByteArray -> Bool
PM.isByteArrayPinned ByteArray
arr = ByteArray
arr
| Bool
otherwise = Bytes -> ByteArray
toPinnedByteArrayClone Bytes
b
toPinnedByteArrayClone :: Bytes -> ByteArray
toPinnedByteArrayClone :: Bytes -> ByteArray
toPinnedByteArrayClone (Bytes ByteArray
arr Int
off Int
len) = (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
m <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
len
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))
m Int
0 ByteArray
arr Int
off 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))
m
toByteString :: Bytes -> ByteString
toByteString :: Bytes -> ByteString
toByteString !Bytes
b = Bytes -> ByteString
pinnedToByteString (Bytes -> Bytes
pin Bytes
b)
pinnedToByteString :: Bytes -> ByteString
pinnedToByteString :: Bytes -> ByteString
pinnedToByteString (Bytes y :: ByteArray
y@(PM.ByteArray ByteArray#
x) Int
off Int
len) =
ForeignPtr Word8 -> Int -> Int -> ByteString
ByteString.PS
( Addr# -> ForeignPtrContents -> ForeignPtr Word8
forall a. Addr# -> ForeignPtrContents -> ForeignPtr a
ForeignPtr.ForeignPtr
(case Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr (ByteArray -> Ptr Word8
PM.byteArrayContents ByteArray
y) Int
off of Exts.Ptr Addr#
p -> Addr#
p)
(MutableByteArray# RealWorld -> ForeignPtrContents
ForeignPtr.PlainPtr (ByteArray# -> MutableByteArray# RealWorld
forall a b. a -> b
Exts.unsafeCoerce# ByteArray#
x))
)
Int
0
Int
len
fromByteString :: ByteString -> Bytes
fromByteString :: ByteString -> Bytes
fromByteString !ByteString
b =
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
$ IO ByteArray -> ST s ByteArray
forall a s. IO a -> ST s a
unsafeIOToST (IO ByteArray -> ST s ByteArray) -> IO ByteArray -> ST s ByteArray
forall a b. (a -> b) -> a -> b
$ do
dst :: MutableByteArray RealWorld
dst@(PM.MutableByteArray MutableByteArray# RealWorld
dst#) <- Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
ByteString.unsafeUseAsCString ByteString
b ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
src -> do
MutablePrimArray (PrimState IO) CChar
-> Int -> CString -> Int -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m ()
PM.copyPtrToMutablePrimArray (MutableByteArray# RealWorld -> MutablePrimArray RealWorld CChar
forall s a. MutableByteArray# s -> MutablePrimArray s a
PM.MutablePrimArray MutableByteArray# RealWorld
dst#) Int
0 CString
src Int
len
MutableByteArray (PrimState IO) -> IO ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray RealWorld
MutableByteArray (PrimState IO)
dst
)
Int
0
Int
len
where
!len :: Int
len = ByteString -> Int
ByteString.length ByteString
b
fromLazyByteString :: LBS.ByteString -> Bytes
fromLazyByteString :: ByteString -> Bytes
fromLazyByteString ByteString
x = case ByteString -> Int64
LBS.length ByteString
x of
Int64
0 -> Bytes
empty
Int64
n64 ->
let n :: Int
n = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n64 :: Int
in 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
$ IO ByteArray -> ST s ByteArray
forall a s. IO a -> ST s a
unsafeIOToST (IO ByteArray -> ST s ByteArray) -> IO ByteArray -> ST s ByteArray
forall a b. (a -> b) -> a -> b
$ do
dst :: MutableByteArray RealWorld
dst@(PM.MutableByteArray MutableByteArray# RealWorld
dst#) <- Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
n
let loop :: ByteString -> Int -> IO ByteArray
loop ByteString
chunks !Int
ix = case ByteString
chunks of
ByteString
LBS.Empty -> MutableByteArray (PrimState IO) -> IO ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray RealWorld
MutableByteArray (PrimState IO)
dst
LBS.Chunk ByteString
c ByteString
cs -> do
let !len :: Int
len = ByteString -> Int
ByteString.length ByteString
c
ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
ByteString.unsafeUseAsCString ByteString
c ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
src -> do
MutablePrimArray (PrimState IO) CChar
-> Int -> CString -> Int -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m ()
PM.copyPtrToMutablePrimArray (MutableByteArray# RealWorld -> MutablePrimArray RealWorld CChar
forall s a. MutableByteArray# s -> MutablePrimArray s a
PM.MutablePrimArray MutableByteArray# RealWorld
dst#) Int
ix CString
src Int
len
ByteString -> Int -> IO ByteArray
loop ByteString
cs (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len)
ByteString -> Int -> IO ByteArray
loop ByteString
x Int
0
)
Int
0
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)
mapU :: (Word8 -> Word8) -> Bytes -> ByteArray
{-# INLINE mapU #-}
mapU :: (Word8 -> Word8) -> Bytes -> ByteArray
mapU Word8 -> Word8
f (Bytes ByteArray
array Int
ix0 Int
len) = (forall s. ST s ByteArray) -> ByteArray
runByteArrayST do
MutableByteArray (PrimState (ST s))
dst <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
let go :: Int -> Int -> ST s ByteArray
go !Int
srcIx !Int
dstIx =
if Int
dstIx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len
then do
let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
array Int
srcIx :: Word8
MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray (PrimState (ST s))
dst Int
dstIx (Word8 -> Word8
f Word8
w)
Int -> Int -> ST s ByteArray
go (Int
srcIx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
dstIx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray (PrimState (ST s))
dst
Int -> Int -> ST s ByteArray
go Int
ix0 Int
0
map :: (Word8 -> Word8) -> Bytes -> Bytes
{-# INLINE map #-}
map :: (Word8 -> Word8) -> Bytes -> Bytes
map Word8 -> Word8
f !Bytes
b = ByteArray -> Int -> Int -> Bytes
Bytes ((Word8 -> Word8) -> Bytes -> ByteArray
mapU Word8 -> Word8
f Bytes
b) Int
0 (Bytes -> Int
length Bytes
b)
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
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
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
toShortByteString :: Bytes -> ShortByteString
{-# INLINE toShortByteString #-}
toShortByteString :: Bytes -> ShortByteString
toShortByteString !Bytes
b = case Bytes -> ByteArray
toByteArray Bytes
b of
PM.ByteArray ByteArray#
x -> ByteArray# -> ShortByteString
SBS ByteArray#
x
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
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 -> Maybe (Bytes, Bytes)
forall a. Maybe a
Nothing
Just Int
n -> (Bytes, Bytes) -> Maybe (Bytes, Bytes)
forall a. a -> Maybe a
Just (Int -> Bytes -> Bytes
unsafeTake Int
n Bytes
b, Int -> Bytes -> Bytes
unsafeDrop (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Bytes
b)
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
4
then Maybe Int
forall a. Maybe a
Nothing
else
let !target :: Word32
target =
Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w0 :: Word32) Int
24
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w1 :: Word32) Int
16
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w2 :: Word32) Int
8
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w3 :: Word32) Int
0
!end :: Int
end = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len
go :: Int -> Word32 -> Maybe Int
go !Int
ix !Word32
acc =
if Word32
acc Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
target
then
let n :: Int
n = Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
off
in Int -> Maybe Int
forall a. a -> Maybe a
Just (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
4)
else
if Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
end
then
let !w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
ix :: Word8
acc' :: Word32
acc' =
(Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w :: Word32)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL Word32
acc Int
8
in Int -> Word32 -> Maybe Int
go (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word32
acc'
else Maybe Int
forall a. Maybe a
Nothing
!acc0 :: Word32
acc0 =
Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
0 :: Word8) :: Word32) Int
24
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
1 :: Word8) :: Word32) Int
16
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
2 :: Word8) :: Word32) Int
8
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteArray -> Int -> Word8
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
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} {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 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 -> t -> t
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) (t
n t -> t -> t
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) = Int -> Int -> Int -> Int
forall {t} {t}. (Ord t, Num t, Num t) => Int -> t -> t -> t
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 -> t -> t
go !Int
off !t
len !t
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 -> t -> t
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) (t
n t -> t -> t
forall a. Num a => a -> a -> a
+ t
1)
else t
n
else t
n
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