module Foundation.Primitive.Block.Mutable
( Block(..)
, MutableBlock(..)
, mutableLengthSize
, mutableLengthBytes
, mutableGetAddr
, new
, newPinned
, isPinned
, iterSet
, read
, write
, unsafeNew
, unsafeWrite
, unsafeRead
, unsafeFreeze
, unsafeThaw
, unsafeCopyElements
, unsafeCopyElementsRO
, unsafeCopyBytes
, unsafeCopyBytesRO
) where
import GHC.Prim
import GHC.Types
import Foundation.Internal.Base
import Foundation.Internal.Proxy
import Foundation.Primitive.Exception
import Foundation.Primitive.Types.OffsetSize
import Foundation.Primitive.Monad
import Foundation.Numerical
import Foundation.Primitive.Types
import Foundation.Primitive.Block.Base
mutableLengthSize :: forall ty st . PrimType ty => MutableBlock ty st -> CountOf ty
mutableLengthSize (MutableBlock mba) =
let !(CountOf (I# szBits)) = primSizeInBytes (Proxy :: Proxy ty)
!elems = quotInt# (sizeofMutableByteArray# mba) szBits
in CountOf (I# elems)
mutableLengthBytes :: MutableBlock ty st -> CountOf Word8
mutableLengthBytes (MutableBlock mba) = CountOf (I# (sizeofMutableByteArray# mba))
isPinned :: MutableBlock ty st -> Bool
isPinned (MutableBlock mba) =
I# (sizeofMutableByteArray# mba) > 3000
mutableGetAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Ptr ty)
mutableGetAddr (MutableBlock mba) = primitive $ \s1 ->
case unsafeFreezeByteArray# mba s1 of
(# s2, ba #) -> (# s2, Ptr (byteArrayContents# ba) #)
iterSet :: (PrimType ty, PrimMonad prim)
=> (Offset ty -> ty)
-> MutableBlock ty (PrimState prim)
-> prim ()
iterSet f ma = loop 0
where
!sz = mutableLengthSize ma
loop i
| i .==# sz = pure ()
| otherwise = unsafeWrite ma i (f i) >> loop (i+1)
read :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> prim ty
read array n
| isOutOfBound n len = primOutOfBound OOB_Read n len
| otherwise = unsafeRead array n
where len = mutableLengthSize array
write :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> ty -> prim ()
write array n val
| isOutOfBound n len = primOutOfBound OOB_Write n len
| otherwise = unsafeWrite array n val
where
len = mutableLengthSize array