hybrid-vectors-0.2.2: Hybrid vectors e.g. Mixed Boxed/Unboxed vectors

Safe HaskellNone
LanguageHaskell98

Data.Vector.Hybrid.Mutable

Contents

Synopsis

Documentation

data MVector :: (* -> * -> *) -> (* -> * -> *) -> * -> * -> * Source #

Instances

(MVector u a, MVector v b) => MVector (MVector u v) (a, b) Source # 

Methods

basicLength :: MVector u v s (a, b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector u v s (a, b) -> MVector u v s (a, b) #

basicOverlaps :: MVector u v s (a, b) -> MVector u v s (a, b) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector u v (PrimState m) (a, b)) #

basicInitialize :: PrimMonad m => MVector u v (PrimState m) (a, b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a, b) -> m (MVector u v (PrimState m) (a, b)) #

basicUnsafeRead :: PrimMonad m => MVector u v (PrimState m) (a, b) -> Int -> m (a, b) #

basicUnsafeWrite :: PrimMonad m => MVector u v (PrimState m) (a, b) -> Int -> (a, b) -> m () #

basicClear :: PrimMonad m => MVector u v (PrimState m) (a, b) -> m () #

basicSet :: PrimMonad m => MVector u v (PrimState m) (a, b) -> (a, b) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector u v (PrimState m) (a, b) -> MVector u v (PrimState m) (a, b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector u v (PrimState m) (a, b) -> MVector u v (PrimState m) (a, b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector u v (PrimState m) (a, b) -> Int -> m (MVector u v (PrimState m) (a, b)) #

Accessors

Length information

length :: MVector u a => MVector u v s (a, b) -> Int Source #

Length of the mutable vector.

null :: MVector u a => MVector u v s (a, b) -> Bool Source #

Check whether the vector is empty

Extracting subvectors

slice :: (MVector u a, MVector v b) => Int -> Int -> MVector u v s (a, b) -> MVector u v s (a, b) Source #

Yield a part of the mutable vector without copying it.

init :: (MVector u a, MVector v b) => MVector u v s (a, b) -> MVector u v s (a, b) Source #

tail :: (MVector u a, MVector v b) => MVector u v s (a, b) -> MVector u v s (a, b) Source #

take :: (MVector u a, MVector v b) => Int -> MVector u v s (a, b) -> MVector u v s (a, b) Source #

drop :: (MVector u a, MVector v b) => Int -> MVector u v s (a, b) -> MVector u v s (a, b) Source #

unsafeSlice Source #

Arguments

:: (MVector u a, MVector v b) 
=> Int

starting index

-> Int

length of the slice

-> MVector u v s (a, b) 
-> MVector u v s (a, b) 

Yield a part of the mutable vector without copying it. No bounds checks are performed.

unsafeInit :: (MVector u a, MVector v b) => MVector u v s (a, b) -> MVector u v s (a, b) Source #

unsafeTail :: (MVector u a, MVector v b) => MVector u v s (a, b) -> MVector u v s (a, b) Source #

unsafeTake :: (MVector u a, MVector v b) => Int -> MVector u v s (a, b) -> MVector u v s (a, b) Source #

unsafeDrop :: (MVector u a, MVector v b) => Int -> MVector u v s (a, b) -> MVector u v s (a, b) Source #

Overlapping

overlaps :: (MVector u a, MVector v b) => MVector u v s (a, b) -> MVector u v s (a, b) -> Bool Source #

Construction

Initialisation

new :: (PrimMonad m, MVector u a, MVector v b) => Int -> m (MVector u v (PrimState m) (a, b)) Source #

Create a mutable vector of the given length.

unsafeNew :: (PrimMonad m, MVector u a, MVector v b) => Int -> m (MVector u v (PrimState m) (a, b)) Source #

Create a mutable vector of the given length. The length is not checked.

replicate :: (PrimMonad m, MVector u a, MVector v b) => Int -> (a, b) -> m (MVector u v (PrimState m) (a, b)) Source #

Create a mutable vector of the given length (0 if the length is negative) and fill it with an initial value.

clone :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> m (MVector u v (PrimState m) (a, b)) Source #

Create a copy of a mutable vector.

Growing

grow :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> m (MVector u v (PrimState m) (a, b)) Source #

Grow a vector by the given number of elements. The number must be positive.

unsafeGrow :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> m (MVector u v (PrimState m) (a, b)) Source #

Grow a vector by the given number of elements. The number must be positive but this is not checked.

Restricting memory usage

clear :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> m () Source #

Reset all elements of the vector to some undefined value, clearing all references to external objects. This is usually a noop for unboxed vectors.

Accessing individual elements

read :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> m (a, b) Source #

Yield the element at the given position.

write :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> (a, b) -> m () Source #

Replace the element at the given position.

swap :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> Int -> m () Source #

Swap the elements at the given positions.

unsafeRead :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> m (a, b) Source #

Yield the element at the given position. No bounds checks are performed.

unsafeWrite :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> (a, b) -> m () Source #

Replace the element at the given position. No bounds checks are performed.

unsafeSwap :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> Int -> Int -> m () Source #

Swap the elements at the given positions. No bounds checks are performed.

Modifying vectors

Filling and copying

set :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> (a, b) -> m () Source #

Set all elements of the vector to the given value.

copy :: (PrimMonad m, MVector u a, MVector v b) => MVector u v (PrimState m) (a, b) -> MVector u v (PrimState m) (a, b) -> m () Source #

Copy a vector. The two vectors must have the same length and may not overlap.

unsafeCopy Source #

Arguments

:: (PrimMonad m, MVector u a, MVector v b) 
=> MVector u v (PrimState m) (a, b)

target

-> MVector u v (PrimState m) (a, b)

source

-> m () 

Copy a vector. The two vectors must have the same length and may not overlap. This is not checked.

Unsafe Construction and deconstruction

unsafeZip :: u s a -> v s b -> MVector u v s (a, b) Source #

The mutable vectors are assumed to be of the same length and to not overlap. This is not checked.

projectFst :: MVector u v s (a, b) -> u s a Source #

projectSnd :: MVector u v s (a, b) -> v s b Source #

Deprecated operations

newWith :: (PrimMonad m, MVector u a, MVector v b) => Int -> (a, b) -> m (MVector u v (PrimState m) (a, b)) Source #

Deprecated: Use replicate instead

DEPRECATED Use replicate instead

unsafeNewWith :: (PrimMonad m, MVector u a, MVector v b) => Int -> (a, b) -> m (MVector u v (PrimState m) (a, b)) Source #

Deprecated: Use replicate instead

DEPRECATED Use replicate instead