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

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.ByteArray

Contents

Synopsis

Types

data ByteArray #

Byte arrays

Constructors

ByteArray ByteArray# 
Instances
IsList ByteArray

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Associated Types

type Item ByteArray :: * #

Eq ByteArray

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Data ByteArray 
Instance details

Defined in Data.Primitive.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

Non-lexicographic ordering. This compares the lengths of the byte arrays first and uses a lexicographic ordering if the lengths are equal. Subject to change between major versions.

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Show ByteArray

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Semigroup ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

Monoid ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

PrimUnlifted ByteArray 
Instance details

Defined in Data.Primitive.UnliftedArray

type Item ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

data MutableByteArray s #

Mutable byte arrays associated with a primitive state token

Instances
Typeable s => Data (MutableByteArray s) 
Instance details

Defined in Data.Primitive.ByteArray

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) 
Instance details

Defined in Data.Primitive.UnliftedArray

Allocation

Element access

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

indexByteArray :: forall a. (HasCallStack, 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

:: (HasCallStack, 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

:: (HasCallStack, 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

:: (HasCallStack, 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

:: (HasCallStack, 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

:: (HasCallStack, 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. This function's behavior is undefined if resizeMutableByteArray is ever called on the mutable byte array given as the argument. Consequently, use of this function is discouraged. Prefer getSizeofMutableByteArray, which ensures correct sequencing in the presence of resizing.

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.