prim-array-0.2.2: Primitive byte array with type variable

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.PrimArray

Contents

Synopsis

Types

data PrimArray a Source #

Primitive arrays

Constructors

PrimArray ByteArray# 

Instances

Prim a => IsList (PrimArray a) Source # 

Associated Types

type Item (PrimArray a) :: * #

Methods

fromList :: [Item (PrimArray a)] -> PrimArray a #

fromListN :: Int -> [Item (PrimArray a)] -> PrimArray a #

toList :: PrimArray a -> [Item (PrimArray a)] #

(Eq a, Prim a) => Eq (PrimArray a) Source # 

Methods

(==) :: PrimArray a -> PrimArray a -> Bool #

(/=) :: PrimArray a -> PrimArray a -> Bool #

(Prim a, Show a) => Show (PrimArray a) Source # 
Prim a => Semigroup (PrimArray a) Source # 

Methods

(<>) :: PrimArray a -> PrimArray a -> PrimArray a #

sconcat :: NonEmpty (PrimArray a) -> PrimArray a #

stimes :: Integral b => b -> PrimArray a -> PrimArray a #

Prim a => Monoid (PrimArray a) Source # 
type Item (PrimArray a) Source # 
type Item (PrimArray a) = a

data MutablePrimArray s a Source #

Mutable primitive arrays associated with a primitive state token

Allocation

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

Element Access

writePrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> a -> m () Source #

indexPrimArray :: forall a. Prim a => PrimArray a -> Int -> a Source #

Read a primitive value from the array.

Freezing and Thawing

unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a) Source #

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

unsafeThawPrimArray :: PrimMonad m => PrimArray a -> m (MutablePrimArray (PrimState m) a) Source #

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

Block Operations

copyPrimArray Source #

Arguments

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

destination array

-> Int

offset into destination array

-> PrimArray a

source array

-> Int

offset into source array

-> Int

number of bytes to copy

-> m () 

Copy part of an array into another mutable array.

copyMutablePrimArray Source #

Arguments

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

destination array

-> Int

offset into destination array

-> MutablePrimArray (PrimState m) a

source array

-> Int

offset into source array

-> Int

number of bytes to copy

-> m () 

Copy part of a mutable array into another mutable array. In the case that the destination and source arrays are the same, the regions may overlap.

copyPrimArrayToPtr Source #

Arguments

:: (PrimMonad m, Prim a) 
=> Ptr a

destination pointer

-> PrimArray a

source array

-> Int

offset into source array

-> Int

number of prims to copy

-> m () 

Copy a slice of an immutable primitive array to an address. The offset and length are given in elements of type a.

copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m () Source #

copyPtrToPrimArray :: forall a. Prim a => Ptr a -> Int -> PrimArray a Source #

setPrimArray Source #

Arguments

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

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.

Information

sameMutablePrimArray :: MutablePrimArray s a -> MutablePrimArray s a -> Bool Source #

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

getSizeofMutablePrimArray Source #

Arguments

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

array

-> m Int 

Get the size of the mutable array.

sizeofPrimArray :: forall a. Prim a => PrimArray a -> Int Source #