primitive-checked-0.6.3.0: primitive functions with bounds-checking

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.ByteArray

Contents

Synopsis

Types

data ByteArray :: * #

Byte arrays

Constructors

ByteArray ByteArray# 

Instances

IsList ByteArray 

Associated Types

type Item ByteArray :: * #

Eq ByteArray 
Data ByteArray 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteArray -> c ByteArray #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteArray #

toConstr :: ByteArray -> Constr #

dataTypeOf :: ByteArray -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ByteArray) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray) #

gmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteArray -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteArray -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray #

Ord ByteArray 
Show ByteArray 
PrimUnlifted ByteArray 
type Item ByteArray 

data MutableByteArray s :: * -> * #

Mutable byte arrays associated with a primitive state token

Instances

Typeable * s => Data (MutableByteArray s) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MutableByteArray s -> c (MutableByteArray s) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableByteArray s) #

toConstr :: MutableByteArray s -> Constr #

dataTypeOf :: MutableByteArray s -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (MutableByteArray s)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MutableByteArray s)) #

gmapT :: (forall b. Data b => b -> b) -> MutableByteArray s -> MutableByteArray s #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MutableByteArray s -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MutableByteArray s -> r #

gmapQ :: (forall d. Data d => d -> u) -> MutableByteArray s -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MutableByteArray s -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MutableByteArray s -> m (MutableByteArray s) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableByteArray s -> m (MutableByteArray s) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableByteArray s -> m (MutableByteArray s) #

PrimUnlifted (MutableByteArray s) 

Allocation

Element access

readByteArray :: forall m a. (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> m a Source #

writeByteArray :: forall m a. (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () Source #

indexByteArray :: forall a. Prim a => ByteArray -> Int -> a Source #

Folding

foldrByteArray :: Prim a => (a -> b -> b) -> b -> ByteArray -> b #

Right-fold over the elements of a ByteArray.

Freezing and thawing

unsafeFreezeByteArray :: PrimMonad m => MutableByteArray (PrimState m) -> m ByteArray #

Convert a mutable byte array to an immutable one without copying. The array should not be modified after the conversion.

unsafeThawByteArray :: PrimMonad m => ByteArray -> m (MutableByteArray (PrimState m)) #

Convert an immutable byte array to a mutable one without copying. The original array should not be used after the conversion.

Block operations

copyByteArray Source #

Arguments

:: PrimMonad m 
=> MutableByteArray (PrimState m)

destination array

-> Int

offset into destination array

-> ByteArray

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

copyMutableByteArray Source #

Arguments

:: PrimMonad m 
=> MutableByteArray (PrimState m)

destination array

-> Int

offset into destination array

-> MutableByteArray (PrimState m)

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

moveByteArray Source #

Arguments

:: PrimMonad m 
=> MutableByteArray (PrimState m)

destination array

-> Int

offset into destination array

-> MutableByteArray (PrimState m)

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

setByteArray Source #

Arguments

:: (Prim a, PrimMonad m) 
=> MutableByteArray (PrimState m)

array to fill

-> Int

offset into array

-> Int

number of values to fill

-> a

value to fill with

-> m () 

fillByteArray Source #

Arguments

:: PrimMonad m 
=> MutableByteArray (PrimState m)

array to fill

-> Int

offset into array

-> Int

number of bytes to fill

-> Word8

byte to fill with

-> m () 

Information

sizeofByteArray :: ByteArray -> Int #

Size of the byte array in bytes.

sizeofMutableByteArray :: MutableByteArray s -> Int #

Size of the mutable byte array in bytes.

sameMutableByteArray :: MutableByteArray s -> MutableByteArray s -> Bool #

Check if the two arrays refer to the same memory block.

byteArrayContents :: ByteArray -> Addr #

Yield a pointer to the array's data. This operation is only safe on pinned byte arrays allocated by newPinnedByteArray or newAlignedPinnedByteArray.

mutableByteArrayContents :: MutableByteArray s -> Addr #

Yield a pointer to the array's data. This operation is only safe on pinned byte arrays allocated by newPinnedByteArray or newAlignedPinnedByteArray.