{-# LANGUAGE UnboxedTuples #-}
module Streamly.Internal.Data.MutByteArray.Type
(
MutByteArray(..)
, MutableByteArray
, getMutableByteArray#
, PinnedState(..)
, isPinned
, pin
, unpin
, empty
, newBytesAs
, new
, pinnedNew
, pinnedNewAlignedBytes
, sizeOfMutableByteArray
, putSliceUnsafe
, cloneSliceUnsafeAs
, cloneSliceUnsafe
, pinnedCloneSliceUnsafe
, unsafePinnedAsPtr
, unsafeAsPtr
, asPtrUnsafe
, nil
) where
import Control.Monad.IO.Class (MonadIO(..))
#ifdef DEBUG
import Control.Monad (when)
import Debug.Trace (trace)
#endif
import GHC.Base (IO(..))
import System.IO.Unsafe (unsafePerformIO)
import GHC.Exts
data PinnedState
= Pinned
| Unpinned deriving (Int -> PinnedState -> ShowS
[PinnedState] -> ShowS
PinnedState -> String
(Int -> PinnedState -> ShowS)
-> (PinnedState -> String)
-> ([PinnedState] -> ShowS)
-> Show PinnedState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PinnedState -> ShowS
showsPrec :: Int -> PinnedState -> ShowS
$cshow :: PinnedState -> String
show :: PinnedState -> String
$cshowList :: [PinnedState] -> ShowS
showList :: [PinnedState] -> ShowS
Show, PinnedState -> PinnedState -> Bool
(PinnedState -> PinnedState -> Bool)
-> (PinnedState -> PinnedState -> Bool) -> Eq PinnedState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PinnedState -> PinnedState -> Bool
== :: PinnedState -> PinnedState -> Bool
$c/= :: PinnedState -> PinnedState -> Bool
/= :: PinnedState -> PinnedState -> Bool
Eq)
data MutByteArray = MutByteArray (MutableByteArray# RealWorld)
{-# DEPRECATED MutableByteArray "Please use MutByteArray instead" #-}
type MutableByteArray = MutByteArray
{-# INLINE getMutableByteArray# #-}
getMutableByteArray# :: MutByteArray -> MutableByteArray# RealWorld
getMutableByteArray# :: MutByteArray -> MutableByteArray# RealWorld
getMutableByteArray# (MutByteArray MutableByteArray# RealWorld
mbarr) = MutableByteArray# RealWorld
mbarr
{-# INLINE sizeOfMutableByteArray #-}
sizeOfMutableByteArray :: MutByteArray -> IO Int
sizeOfMutableByteArray :: MutByteArray -> IO Int
sizeOfMutableByteArray (MutByteArray MutableByteArray# RealWorld
arr) =
(State# RealWorld -> (# State# RealWorld, Int #)) -> IO Int
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, Int #)) -> IO Int)
-> (State# RealWorld -> (# State# RealWorld, Int #)) -> IO Int
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case MutableByteArray# RealWorld
-> State# RealWorld -> (# State# RealWorld, Int# #)
forall d. MutableByteArray# d -> State# d -> (# State# d, Int# #)
getSizeofMutableByteArray# MutableByteArray# RealWorld
arr State# RealWorld
s of
(# State# RealWorld
s1, Int#
i #) -> (# State# RealWorld
s1, Int# -> Int
I# Int#
i #)
{-# INLINE touch #-}
touch :: MutByteArray -> IO ()
touch :: MutByteArray -> IO ()
touch (MutByteArray MutableByteArray# RealWorld
contents) =
(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> case MutableByteArray# RealWorld -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# MutableByteArray# RealWorld
contents State# RealWorld
s of State# RealWorld
s' -> (# State# RealWorld
s', () #)
{-# INLINE unsafePinnedAsPtr #-}
unsafePinnedAsPtr :: MonadIO m => MutByteArray -> (Ptr a -> m b) -> m b
unsafePinnedAsPtr :: forall (m :: * -> *) a b.
MonadIO m =>
MutByteArray -> (Ptr a -> m b) -> m b
unsafePinnedAsPtr MutByteArray
arr Ptr a -> m b
f = do
MutByteArray
contents <- IO MutByteArray -> m MutByteArray
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutByteArray -> m MutByteArray)
-> IO MutByteArray -> m MutByteArray
forall a b. (a -> b) -> a -> b
$ MutByteArray -> IO MutByteArray
pin MutByteArray
arr
let !ptr :: Ptr a
ptr = Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Addr#
byteArrayContents#
(MutableByteArray# RealWorld -> ByteArray#
forall a b. a -> b
unsafeCoerce# (MutByteArray -> MutableByteArray# RealWorld
getMutableByteArray# MutByteArray
contents)))
b
r <- Ptr a -> m b
f Ptr a
forall {a}. Ptr a
ptr
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ MutByteArray -> IO ()
touch MutByteArray
contents
b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return b
r
{-# DEPRECATED asPtrUnsafe "Please use unsafePinnedAsPtr instead." #-}
{-# INLINE asPtrUnsafe #-}
asPtrUnsafe :: MonadIO m => MutByteArray -> (Ptr a -> m b) -> m b
asPtrUnsafe :: forall (m :: * -> *) a b.
MonadIO m =>
MutByteArray -> (Ptr a -> m b) -> m b
asPtrUnsafe = MutByteArray -> (Ptr a -> m b) -> m b
forall (m :: * -> *) a b.
MonadIO m =>
MutByteArray -> (Ptr a -> m b) -> m b
unsafePinnedAsPtr
{-# INLINE unsafeAsPtr #-}
unsafeAsPtr :: MonadIO m => MutByteArray -> (Ptr a -> m b) -> m b
unsafeAsPtr :: forall (m :: * -> *) a b.
MonadIO m =>
MutByteArray -> (Ptr a -> m b) -> m b
unsafeAsPtr MutByteArray
arr Ptr a -> m b
f = do
let !ptr :: Ptr a
ptr = Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Addr#
byteArrayContents#
(MutableByteArray# RealWorld -> ByteArray#
forall a b. a -> b
unsafeCoerce# (MutByteArray -> MutableByteArray# RealWorld
getMutableByteArray# MutByteArray
arr)))
b
r <- Ptr a -> m b
f Ptr a
forall {a}. Ptr a
ptr
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ MutByteArray -> IO ()
touch MutByteArray
arr
b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return b
r
{-# NOINLINE empty #-}
empty :: MutByteArray
empty :: MutByteArray
empty = IO MutByteArray -> MutByteArray
forall a. IO a -> a
unsafePerformIO (IO MutByteArray -> MutByteArray)
-> IO MutByteArray -> MutByteArray
forall a b. (a -> b) -> a -> b
$ Int -> IO MutByteArray
new Int
0
{-# DEPRECATED nil "Please use empty instead" #-}
nil :: MutByteArray
nil :: MutByteArray
nil = MutByteArray
empty
{-# INLINE new #-}
new :: Int -> IO MutByteArray
new :: Int -> IO MutByteArray
new Int
nbytes | Int
nbytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
String -> IO MutByteArray
forall a. String -> a
errorWithoutStackTrace String
"newByteArray: size must be >= 0"
new (I# Int#
nbytes) = (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
nbytes State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr# #) ->
let c :: MutByteArray
c = MutableByteArray# RealWorld -> MutByteArray
MutByteArray MutableByteArray# RealWorld
mbarr#
in (# State# RealWorld
s', MutByteArray
c #)
{-# INLINE pinnedNew #-}
pinnedNew :: Int -> IO MutByteArray
pinnedNew :: Int -> IO MutByteArray
pinnedNew Int
nbytes | Int
nbytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
String -> IO MutByteArray
forall a. String -> a
errorWithoutStackTrace String
"pinnedNew: size must be >= 0"
pinnedNew (I# Int#
nbytes) = (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newPinnedByteArray# Int#
nbytes State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr# #) ->
let c :: MutByteArray
c = MutableByteArray# RealWorld -> MutByteArray
MutByteArray MutableByteArray# RealWorld
mbarr#
in (# State# RealWorld
s', MutByteArray
c #)
{-# INLINE pinnedNewAlignedBytes #-}
pinnedNewAlignedBytes :: Int -> Int -> IO MutByteArray
pinnedNewAlignedBytes :: Int -> Int -> IO MutByteArray
pinnedNewAlignedBytes Int
nbytes Int
_align | Int
nbytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
String -> IO MutByteArray
forall a. String -> a
errorWithoutStackTrace String
"pinnedNewAlignedBytes: size must be >= 0"
pinnedNewAlignedBytes (I# Int#
nbytes) (I# Int#
align) = (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d.
Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
newAlignedPinnedByteArray# Int#
nbytes Int#
align State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr# #) ->
let c :: MutByteArray
c = MutableByteArray# RealWorld -> MutByteArray
MutByteArray MutableByteArray# RealWorld
mbarr#
in (# State# RealWorld
s', MutByteArray
c #)
{-# INLINE newBytesAs #-}
newBytesAs :: PinnedState -> Int -> IO MutByteArray
newBytesAs :: PinnedState -> Int -> IO MutByteArray
newBytesAs PinnedState
Unpinned = Int -> IO MutByteArray
new
newBytesAs PinnedState
Pinned = Int -> IO MutByteArray
pinnedNew
{-# INLINE putSliceUnsafe #-}
putSliceUnsafe ::
MonadIO m
=> MutByteArray
-> Int
-> MutByteArray
-> Int
-> Int
-> m ()
putSliceUnsafe :: forall (m :: * -> *).
MonadIO m =>
MutByteArray -> Int -> MutByteArray -> Int -> Int -> m ()
putSliceUnsafe MutByteArray
src Int
srcStartBytes MutByteArray
dst Int
dstStartBytes Int
lenBytes = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
#ifdef DEBUG
srcLen <- sizeOfMutableByteArray src
dstLen <- sizeOfMutableByteArray dst
when (srcLen - srcStartBytes < lenBytes)
$ error $ "putSliceUnsafe: src overflow: start" ++ show srcStartBytes
++ " end " ++ show srcLen ++ " len " ++ show lenBytes
when (dstLen - dstStartBytes < lenBytes)
$ error $ "putSliceUnsafe: dst overflow: start" ++ show dstStartBytes
++ " end " ++ show dstLen ++ " len " ++ show lenBytes
#endif
let !(I# Int#
srcStartBytes#) = Int
srcStartBytes
!(I# Int#
dstStartBytes#) = Int
dstStartBytes
!(I# Int#
lenBytes#) = Int
lenBytes
let arrS# :: MutableByteArray# RealWorld
arrS# = MutByteArray -> MutableByteArray# RealWorld
getMutableByteArray# MutByteArray
src
arrD# :: MutableByteArray# RealWorld
arrD# = MutByteArray -> MutableByteArray# RealWorld
getMutableByteArray# MutByteArray
dst
(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s# -> (# MutableByteArray# RealWorld
-> Int#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray#
MutableByteArray# RealWorld
arrS# Int#
srcStartBytes# MutableByteArray# RealWorld
arrD# Int#
dstStartBytes# Int#
lenBytes# State# RealWorld
s#
, () #)
{-# INLINE cloneSliceUnsafeAs #-}
cloneSliceUnsafeAs :: MonadIO m =>
PinnedState -> Int -> Int -> MutByteArray -> m MutByteArray
cloneSliceUnsafeAs :: forall (m :: * -> *).
MonadIO m =>
PinnedState -> Int -> Int -> MutByteArray -> m MutByteArray
cloneSliceUnsafeAs PinnedState
ps Int
srcOff Int
srcLen MutByteArray
src =
IO MutByteArray -> m MutByteArray
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutByteArray -> m MutByteArray)
-> IO MutByteArray -> m MutByteArray
forall a b. (a -> b) -> a -> b
$ do
MutByteArray
mba <- PinnedState -> Int -> IO MutByteArray
newBytesAs PinnedState
ps Int
srcLen
MutByteArray -> Int -> MutByteArray -> Int -> Int -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutByteArray -> Int -> MutByteArray -> Int -> Int -> m ()
putSliceUnsafe MutByteArray
src Int
srcOff MutByteArray
mba Int
0 Int
srcLen
MutByteArray -> IO MutByteArray
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MutByteArray
mba
{-# INLINE cloneSliceUnsafe #-}
cloneSliceUnsafe :: MonadIO m => Int -> Int -> MutByteArray -> m MutByteArray
cloneSliceUnsafe :: forall (m :: * -> *).
MonadIO m =>
Int -> Int -> MutByteArray -> m MutByteArray
cloneSliceUnsafe = PinnedState -> Int -> Int -> MutByteArray -> m MutByteArray
forall (m :: * -> *).
MonadIO m =>
PinnedState -> Int -> Int -> MutByteArray -> m MutByteArray
cloneSliceUnsafeAs PinnedState
Unpinned
{-# INLINE pinnedCloneSliceUnsafe #-}
pinnedCloneSliceUnsafe :: MonadIO m =>
Int -> Int -> MutByteArray -> m MutByteArray
pinnedCloneSliceUnsafe :: forall (m :: * -> *).
MonadIO m =>
Int -> Int -> MutByteArray -> m MutByteArray
pinnedCloneSliceUnsafe = PinnedState -> Int -> Int -> MutByteArray -> m MutByteArray
forall (m :: * -> *).
MonadIO m =>
PinnedState -> Int -> Int -> MutByteArray -> m MutByteArray
cloneSliceUnsafeAs PinnedState
Pinned
{-# INLINE isPinned #-}
isPinned :: MutByteArray -> Bool
isPinned :: MutByteArray -> Bool
isPinned (MutByteArray MutableByteArray# RealWorld
arr#) =
let pinnedInt :: Int
pinnedInt = Int# -> Int
I# (MutableByteArray# RealWorld -> Int#
forall d. MutableByteArray# d -> Int#
isMutableByteArrayPinned# MutableByteArray# RealWorld
arr#)
in Int
pinnedInt Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0
{-# INLINE cloneMutableArrayWith# #-}
cloneMutableArrayWith#
:: (Int# -> State# RealWorld -> (# State# RealWorld
, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# :: (Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
alloc# MutableByteArray# RealWorld
arr# State# RealWorld
s# =
case MutableByteArray# RealWorld
-> State# RealWorld -> (# State# RealWorld, Int# #)
forall d. MutableByteArray# d -> State# d -> (# State# d, Int# #)
getSizeofMutableByteArray# MutableByteArray# RealWorld
arr# State# RealWorld
s# of
(# State# RealWorld
s1#, Int#
i# #) ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
alloc# Int#
i# State# RealWorld
s1# of
(# State# RealWorld
s2#, MutableByteArray# RealWorld
arr1# #) ->
case MutableByteArray# RealWorld
-> Int#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray# MutableByteArray# RealWorld
arr# Int#
0# MutableByteArray# RealWorld
arr1# Int#
0# Int#
i# State# RealWorld
s2# of
State# RealWorld
s3# -> (# State# RealWorld
s3#, MutableByteArray# RealWorld
arr1# #)
{-# INLINE pin #-}
pin :: MutByteArray -> IO MutByteArray
pin :: MutByteArray -> IO MutByteArray
pin arr :: MutByteArray
arr@(MutByteArray MutableByteArray# RealWorld
marr#) =
if MutByteArray -> Bool
isPinned MutByteArray
arr
then MutByteArray -> IO MutByteArray
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MutByteArray
arr
else
#ifdef DEBUG
do
trace ("pin: Copying array") (return ())
#endif
(State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO
((State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s# ->
case (Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newPinnedByteArray# MutableByteArray# RealWorld
marr# State# RealWorld
s# of
(# State# RealWorld
s1#, MutableByteArray# RealWorld
marr1# #) -> (# State# RealWorld
s1#, MutableByteArray# RealWorld -> MutByteArray
MutByteArray MutableByteArray# RealWorld
marr1# #)
{-# INLINE unpin #-}
unpin :: MutByteArray -> IO MutByteArray
unpin :: MutByteArray -> IO MutByteArray
unpin arr :: MutByteArray
arr@(MutByteArray MutableByteArray# RealWorld
marr#) =
if Bool -> Bool
not (MutByteArray -> Bool
isPinned MutByteArray
arr)
then MutByteArray -> IO MutByteArray
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MutByteArray
arr
else
#ifdef DEBUG
do
trace ("unpin: Copying array") (return ())
#endif
(State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO
((State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutByteArray #))
-> IO MutByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s# ->
case (Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# MutableByteArray# RealWorld
marr# State# RealWorld
s# of
(# State# RealWorld
s1#, MutableByteArray# RealWorld
marr1# #) -> (# State# RealWorld
s1#, MutableByteArray# RealWorld -> MutByteArray
MutByteArray MutableByteArray# RealWorld
marr1# #)