primitive-checked-0.7.3.0: primitive functions with bounds-checking
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.ByteArray

Synopsis

Types

data ByteArray #

Byte arrays.

Constructors

ByteArray ByteArray# 

Instances

Instances details
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 :: forall r r'. (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

Behavior changed in 0.7.2.0. Before 0.7.2.0, this instance rendered 8-bit words less than 16 as a single hexadecimal digit (e.g. 13 was 0xD). Starting with 0.7.2.0, all 8-bit words are represented as two digits (e.g. 13 is 0x0D).

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

NFData ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

Methods

rnf :: ByteArray -> () #

type Item ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

data MutableByteArray s #

Mutable byte arrays associated with a primitive state token.

Instances

Instances details
Eq (MutableByteArray s) 
Instance details

Defined in Data.Primitive.ByteArray

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 :: forall r r'. (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) #

NFData (MutableByteArray s) 
Instance details

Defined in Data.Primitive.ByteArray

Methods

rnf :: MutableByteArray s -> () #

Allocation

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

After a call to resizeMutableByteArray, the original reference to the mutable array should not be used again. This cannot truly be enforced except by linear types. To attempt to enforce this, we always make a copy of the mutable primitive array and intentionally corrupt the original of the original one. The strategy used here to corrupt the array is simply to write 0xFF to every byte.

shrinkMutableByteArray Source #

Arguments

:: (HasCallStack, PrimMonad m) 
=> MutableByteArray (PrimState m) 
-> Int

new size

-> m () 

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 #

Constructing

byteArrayFromList :: Prim a => [a] -> ByteArray #

Create a ByteArray from a list.

byteArrayFromList xs = byteArrayFromListN (length xs) xs

byteArrayFromListN :: Prim a => Int -> [a] -> ByteArray #

Create a ByteArray from a list of a known length. If the length of the list does not match the given length, this throws an exception.

Folding

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

Right-fold over the elements of a ByteArray.

Comparing

Freezing and thawing

freezeByteArray Source #

Arguments

:: (HasCallStack, PrimMonad m) 
=> MutableByteArray (PrimState m)

source

-> Int

offset

-> Int

length

-> m ByteArray 

thawByteArray Source #

Arguments

:: (HasCallStack, PrimMonad m) 
=> ByteArray

source

-> Int

offset

-> Int

length

-> m (MutableByteArray (PrimState m)) 

runByteArray :: (forall s. ST s (MutableByteArray s)) -> ByteArray #

Execute the monadic action and freeze the resulting array.

runByteArray m = runST $ m >>= unsafeFreezeByteArray

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

This corrupts the contents of the argument array by writing 0xFF to every byte.

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

:: forall m. (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

:: forall m. (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 () 

copyByteArrayToPtr Source #

Arguments

:: forall m a. (HasCallStack, PrimMonad m, Prim a) 
=> Ptr a

destination pointer

-> ByteArray

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

copyMutableByteArrayToPtr Source #

Arguments

:: forall m a. (HasCallStack, PrimMonad m, Prim a) 
=> Ptr a

destination pointer

-> MutableByteArray (PrimState m)

source array

-> Int

offset into source array

-> Int

number of elements to copy

-> m () 

copyByteArrayToAddr Source #

Arguments

:: (HasCallStack, PrimMonad m) 
=> Ptr Word8

destination pointer

-> ByteArray

source array

-> Int

offset into source array

-> Int

number of bytes to copy

-> m () 

copyMutableByteArrayToAddr Source #

Arguments

:: (HasCallStack, PrimMonad m) 
=> Ptr Word8

destination pointer

-> MutableByteArray (PrimState m)

source array

-> Int

offset into source array

-> Int

number of bytes to copy

-> m () 

moveByteArray Source #

Arguments

:: forall m. (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 bytes to copy

-> m () 

setByteArray Source #

Arguments

:: forall m a. (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 () 

cloneByteArray Source #

Arguments

:: HasCallStack 
=> ByteArray

source array

-> Int

offset into source array

-> Int

number of bytes to copy

-> ByteArray 

cloneMutableByteArray Source #

Arguments

:: (HasCallStack, PrimMonad m) 
=> MutableByteArray (PrimState m)

source array

-> Int

offset into source array

-> Int

number of bytes to copy

-> m (MutableByteArray (PrimState 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.

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

Get the size of a byte array in bytes. Unlike sizeofMutableByteArray, this function ensures sequencing in the presence of resizing.

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

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

isByteArrayPinned :: ByteArray -> Bool #

Check whether or not the byte array is pinned. Pinned byte arrays cannot be moved by the garbage collector. It is safe to use byteArrayContents on such byte arrays. This function is only available when compiling with GHC 8.2 or newer.

Since: primitive-0.6.4.0

isMutableByteArrayPinned :: MutableByteArray s -> Bool #

Check whether or not the mutable byte array is pinned. This function is only available when compiling with GHC 8.2 or newer.

Since: primitive-0.6.4.0

byteArrayContents :: ByteArray -> Ptr Word8 #

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 -> Ptr Word8 #

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