{-# language BangPatterns #-}
{-# language BlockArguments #-}
{-# language MagicHash #-}
{-# language NamedFieldPuns #-}
{-# language TypeApplications #-}
{-# language UnboxedTuples #-}
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
, unsafeDrop
, unsafeTake
, unsafeIndex
, unsafeHead
, map
, mapU
, null
, toShortByteString
) where
import Prelude hiding (Foldable(..),map)
import Control.Monad.Primitive (PrimState,PrimMonad)
import Control.Monad.ST.Run (runByteArrayST)
import Data.Bits (xor)
import Data.Bytes.Types (Bytes(Bytes))
import Data.ByteString (ByteString)
import Data.ByteString.Short.Internal (ShortByteString(SBS))
import Data.Primitive (ByteArray(ByteArray),MutableByteArray,PrimArray(PrimArray))
import Data.Word (Word64,Word32,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.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 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
(forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
0 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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
(forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
0 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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 <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
unsafeCopy MutableByteArray s
dst Int
0 Bytes
b
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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 forall a. Eq a => a -> a -> Bool
== Int
0, ByteArray -> Int
PM.sizeofByteArray ByteArray
arr 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 a b. (a -> b) -> a -> b
$ do
MutableByteArray s
m <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
m Int
0 ByteArray
arr Int
off Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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) =
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 (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 = 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 forall a. Bits a => a -> a -> a
`xor` Word32
acc) forall a. Num a => a -> a -> a
* Word32
0x01000193
) Word32
0x811c9dc5 Bytes
b
fnv1a64 :: Bytes -> Word64
fnv1a64 :: Bytes -> Word64
fnv1a64 !Bytes
b = 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 forall a. Bits a => a -> a -> a
`xor` Word64
acc) 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) =
forall {t}. (Eq t, Num t) => Int -> t -> a
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)
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 forall a. Num a => a -> a -> a
- Int
1) (t
ix forall a. Num a => a -> a -> a
- t
1)) (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) = 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 (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)) (Int
off forall a. Num a => a -> a -> a
+ Int
1) (t
len 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) = 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 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
t
_ -> do
a
a' <- a -> Word8 -> m a
f a
a (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)
a -> Int -> t -> m a
go a
a' (Int
off forall a. Num a => a -> a -> a
+ Int
1) (t
len 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) = 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 (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off) (Int -> t -> a
go (Int
off forall a. Num a => a -> a -> a
+ Int
1) (t
len 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) = 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 (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off)) (Int
ix forall a. Num a => a -> a -> a
+ Int
1) (Int
off forall a. Num a => a -> a -> a
+ Int
1) (t
len 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) =
forall {t}. (Eq t, Num t) => a -> Int -> t -> a
go a
a0 (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)
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 (forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr Int
off) a
a) (Int
off forall a. Num a => a -> a -> a
- Int
1) (t
ix 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) =
forall {t}. (Eq t, Num t) => a -> Int -> t -> m a
go a
a0 (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)
where
go :: a -> Int -> t -> m a
go !a
a !Int
off !t
ix = case t
ix of
(-1) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
t
_ -> do
a
a' <- Word8 -> a -> m a
f (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 forall a. Num a => a -> a -> a
- Int
1) (t
ix 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
_) = 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 forall a. Eq a => a -> a -> Bool
== Int
0, ByteArray -> Int
PM.sizeofByteArray ByteArray
arr 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 a b. (a -> b) -> a -> b
$ do
MutableByteArray s
m <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newPinnedByteArray Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
m Int
0 ByteArray
arr Int
off Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray 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
(forall a. Addr# -> ForeignPtrContents -> ForeignPtr a
ForeignPtr.ForeignPtr
(case 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 (unsafeCoerce# :: 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 a b. (a -> b) -> a -> b
$ forall a s. IO a -> ST s a
unsafeIOToST forall a b. (a -> b) -> a -> b
$ do
dst :: MutableByteArray RealWorld
dst@(PM.MutableByteArray MutableByteArray# RealWorld
dst# ) <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
len
forall a. ByteString -> (CString -> IO a) -> IO a
ByteString.unsafeUseAsCString ByteString
b forall a b. (a -> b) -> a -> b
$ \CString
src -> do
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# RealWorld
dst# ) Int
0 CString
src Int
len
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray RealWorld
dst
) Int
0 Int
len
where
!len :: Int
len = ByteString -> Int
ByteString.length ByteString
b
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 forall a. Num a => a -> a -> a
+ Int
n) (Int
len 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 <- 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 forall a. Ord a => a -> a -> Bool
< Int
len
then do
let w :: Word8
w = forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
array Int
srcIx :: Word8
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 forall a. Num a => a -> a -> a
+ Int
1) (Int
dstIx forall a. Num a => a -> a -> a
+ Int
1)
else 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 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 = forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray ByteArray
arr (Int
off 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