primitive-0.6.2.0: Primitive memory-related operations

Copyright(c) Roman Leshchinskiy 2009-2012
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.ByteArray

Contents

Description

Primitive operations on ByteArrays

Synopsis

Types

data ByteArray Source #

Byte arrays

Constructors

ByteArray ByteArray# 

Instances

Data ByteArray Source # 

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 #

PrimUnlifted ByteArray Source # 

data MutableByteArray s Source #

Mutable byte arrays associated with a primitive state token

Instances

Typeable * s => Data (MutableByteArray s) Source # 

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) Source # 

data ByteArray# :: (#) #

data MutableByteArray# a :: * -> (#) #

Allocation

newByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m)) Source #

Create a new mutable byte array of the specified size.

newPinnedByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m)) Source #

Create a pinned byte array of the specified size. The garbage collector is guaranteed not to move it.

newAlignedPinnedByteArray :: PrimMonad m => Int -> Int -> m (MutableByteArray (PrimState m)) Source #

Create a pinned byte array of the specified size and with the give alignment. The garbage collector is guaranteed not to move it.

Element access

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

Read a primitive value from the byte array. The offset is given in elements of type a rather than in bytes.

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

Write a primitive value to the byte array. The offset is given in elements of type a rather than in bytes.

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

Read a primitive value from the byte array. The offset is given in elements of type a rather than in bytes.

Freezing and thawing

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

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)) Source #

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 bytes to copy

-> m () 

Copy a slice of an immutable byte array to a mutable byte array.

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 bytes to copy

-> m () 

Copy a slice of a mutable byte array into another array. The two slices may not overlap.

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 bytes to copy

-> m () 

Copy a slice of a mutable byte array into another, potentially overlapping array.

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 () 

Fill a slice of a mutable byte array with a value. The offset and length are given in elements of type a rather than in bytes.

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 () 

Fill a slice of a mutable byte array with a byte.

Information

sizeofByteArray :: ByteArray -> Int Source #

Size of the byte array.

sizeofMutableByteArray :: MutableByteArray s -> Int Source #

Size of the mutable byte array.

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

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

byteArrayContents :: ByteArray -> Addr Source #

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 Source #

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