Z-Data-0.1.4.2: Array, vector and text

Safe HaskellNone
LanguageHaskell2010

Z.Data.Array.UnliftedArray

Synopsis

Documentation

class PrimUnlifted a where Source #

Instances
PrimUnlifted ByteArray Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (IORef a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (MVar a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (PrimArray a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (MutableByteArray s) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (STRef s a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (MutablePrimArray s a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

data UnliftedArray a Source #

Instances
PrimUnlifted a => Arr UnliftedArray a Source # 
Instance details

Defined in Z.Data.Array

Associated Types

type MArr UnliftedArray = (mar :: Type -> Type -> Type) Source #

Methods

newArr :: (PrimMonad m, PrimState m ~ s) => Int -> m (MArr UnliftedArray s a) Source #

newArrWith :: (PrimMonad m, PrimState m ~ s) => Int -> a -> m (MArr UnliftedArray s a) Source #

readArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> m a Source #

writeArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> a -> m () Source #

setArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> Int -> a -> m () Source #

indexArr :: UnliftedArray a -> Int -> a Source #

indexArr' :: UnliftedArray a -> Int -> (#a#) Source #

indexArrM :: Monad m => UnliftedArray a -> Int -> m a Source #

freezeArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> Int -> m (UnliftedArray a) Source #

thawArr :: (PrimMonad m, PrimState m ~ s) => UnliftedArray a -> Int -> Int -> m (MArr UnliftedArray s a) Source #

unsafeFreezeArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> m (UnliftedArray a) Source #

unsafeThawArr :: (PrimMonad m, PrimState m ~ s) => UnliftedArray a -> m (MArr UnliftedArray s a) Source #

copyArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> UnliftedArray a -> Int -> Int -> m () Source #

copyMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> MArr UnliftedArray s a -> Int -> Int -> m () Source #

moveArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> MArr UnliftedArray s a -> Int -> Int -> m () Source #

cloneArr :: UnliftedArray a -> Int -> Int -> UnliftedArray a Source #

cloneMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> Int -> m (MArr UnliftedArray s a) Source #

resizeMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> m (MArr UnliftedArray s a) Source #

shrinkMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> Int -> m () Source #

sameMutableArr :: MArr UnliftedArray s a -> MArr UnliftedArray s a -> Bool Source #

sizeofArr :: UnliftedArray a -> Int Source #

sizeofMutableArr :: (PrimMonad m, PrimState m ~ s) => MArr UnliftedArray s a -> m Int Source #

sameArr :: UnliftedArray a -> UnliftedArray a -> Bool Source #

PrimUnlifted a => Vec UnliftedArray a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray UnliftedArray :: Type -> Type Source #

type MArr UnliftedArray Source # 
Instance details

Defined in Z.Data.Array

type IArray UnliftedArray Source # 
Instance details

Defined in Z.Data.Vector.Base

unsafeNewUnliftedArray Source #

Arguments

:: PrimMonad m 
=> Int

size

-> m (MutableUnliftedArray (PrimState m) a) 

Creates a new MutableUnliftedArray. This function is unsafe because it initializes all elements of the array as pointers to the array itself. Attempting to read one of these elements before writing to it is in effect an unsafe coercion from the MutableUnliftedArray s a to the element type.

newUnliftedArray Source #

Arguments

:: (PrimMonad m, PrimUnlifted a) 
=> Int

size

-> a

initial value

-> m (MutableUnliftedArray (PrimState m) a) 

Creates a new MutableUnliftedArray with the specified value as initial contents. This is slower than unsafeNewUnliftedArray, but safer.

setUnliftedArray Source #

Arguments

:: (PrimMonad m, PrimUnlifted a) 
=> MutableUnliftedArray (PrimState m) a

destination

-> Int

offset

-> Int

length

-> a

value to fill with

-> m () 

sizeofUnliftedArray :: UnliftedArray e -> Int Source #

Yields the length of an UnliftedArray.

unsafeFreezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> m (UnliftedArray a) Source #

Freezes a MutableUnliftedArray, yielding an UnliftedArray. This simply marks the array as frozen in place, so it should only be used when no further modifications to the mutable array will be performed.

sameMutableUnliftedArray :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool Source #

Determines whether two MutableUnliftedArray values are the same. This is object/pointer identity, not based on the contents.

copyUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

destination

-> Int

offset into destination

-> UnliftedArray a

source

-> Int

offset into source

-> Int

number of elements to copy

-> m () 

Copies the contents of an immutable array into a mutable array.

copyMutableUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

destination

-> Int

offset into destination

-> MutableUnliftedArray (PrimState m) a

source

-> Int

offset into source

-> Int

number of elements to copy

-> m () 

Copies the contents of one mutable array into another.

freezeUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

source

-> Int

offset

-> Int

length

-> m (UnliftedArray a) 

Freezes a portion of a MutableUnliftedArray, yielding an UnliftedArray. This operation is safe, in that it copies the frozen portion, and the existing mutable array may still be used afterward.

thawUnliftedArray Source #

Arguments

:: PrimMonad m 
=> UnliftedArray a

source

-> Int

offset

-> Int

length

-> m (MutableUnliftedArray (PrimState m) a) 

Thaws a portion of an UnliftedArray, yielding a MutableUnliftedArray. This copies the thawed portion, so mutations will not affect the original array.

cloneUnliftedArray Source #

Arguments

:: UnliftedArray a

source

-> Int

offset

-> Int

length

-> UnliftedArray a 

Creates a copy of a portion of an UnliftedArray

cloneMutableUnliftedArray Source #

Arguments

:: PrimMonad m 
=> MutableUnliftedArray (PrimState m) a

source

-> Int

offset

-> Int

length

-> m (MutableUnliftedArray (PrimState m) a) 

Creates a new MutableUnliftedArray containing a copy of a portion of another mutable array.