vector-0.5: Efficient Arrays

Portabilitynon-portable
Stabilityexperimental
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>

Data.Vector.Generic.Mutable

Contents

Description

Generic interface to mutable vectors

Synopsis

Class of mutable vector types

class MVector v a whereSource

Class of mutable vectors parametrised with a primitive state token.

Methods

basicLength :: v s a -> IntSource

Length of the mutable vector. This method should not be called directly, use length instead.

basicUnsafeSliceSource

Arguments

:: Int

starting index

-> Int

length of the slice

-> v s a 
-> v s a 

Yield a part of the mutable vector without copying it. This method should not be called directly, use unsafeSlice instead.

basicOverlaps :: v s a -> v s a -> BoolSource

basicUnsafeNew :: PrimMonad m => Int -> m (v (PrimState m) a)Source

Create a mutable vector of the given length. This method should not be called directly, use unsafeNew instead.

basicUnsafeNewWith :: PrimMonad m => Int -> a -> m (v (PrimState m) a)Source

Create a mutable vector of the given length and fill it with an initial value. This method should not be called directly, use unsafeNewWith instead.

basicUnsafeRead :: PrimMonad m => v (PrimState m) a -> Int -> m aSource

Yield the element at the given position. This method should not be called directly, use unsafeRead instead.

basicUnsafeWrite :: PrimMonad m => v (PrimState m) a -> Int -> a -> m ()Source

Replace the element at the given position. This method should not be called directly, use unsafeWrite instead.

basicClear :: PrimMonad m => v (PrimState m) a -> 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. This method should not be called directly, use clear instead.

basicSet :: PrimMonad m => v (PrimState m) a -> a -> m ()Source

Set all elements of the vector to the given value. This method should not be called directly, use set instead.

basicUnsafeCopySource

Arguments

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

target

-> v (PrimState m) a

source

-> m () 

Copy a vector. The two vectors may not overlap. This method should not be called directly, use unsafeCopy instead.

basicUnsafeGrow :: PrimMonad m => v (PrimState m) a -> Int -> m (v (PrimState m) a)Source

Grow a vector by the given number of elements. This method should not be called directly, use unsafeGrow instead.

Operations on mutable vectors

length :: MVector v a => v s a -> IntSource

Length of the mutable vector.

overlaps :: MVector v a => v s a -> v s a -> BoolSource

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

Create a mutable vector of the given length.

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

Create a mutable vector of the given length and fill it with an initial value.

read :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m aSource

Yield the element at the given position.

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

Replace the element at the given position.

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

Swap the elements at the given positions.

clear :: (PrimMonad m, MVector v a) => v (PrimState m) a -> 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.

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

Set all elements of the vector to the given value.

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

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

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

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

slice :: MVector v a => Int -> Int -> v s a -> v s aSource

Yield a part of the mutable vector without copying it.

take :: MVector v a => Int -> v s a -> v s aSource

drop :: MVector v a => Int -> v s a -> v s aSource

init :: MVector v a => v s a -> v s aSource

tail :: MVector v a => v s a -> v s aSource

unsafeSliceSource

Arguments

:: MVector v a 
=> Int

starting index

-> Int

length of the slice

-> v s a 
-> v s a 

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

unsafeInit :: MVector v a => v s a -> v s aSource

unsafeTail :: MVector v a => v s a -> v s aSource

Unsafe operations

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

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

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

Create a mutable vector of the given length and fill it with an initial value. The length is not checked.

unsafeRead :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m aSource

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

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

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

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

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

unsafeCopySource

Arguments

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

target

-> v (PrimState m) a

source

-> m () 

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

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

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

Internal operations

unstream :: (PrimMonad m, MVector v a) => Stream a -> m (v (PrimState m) a)Source

Create a new mutable vector and fill it with elements from the Stream. The vector will grow logarithmically if the Size hint of the Stream is inexact.

transform :: (PrimMonad m, MVector v a) => (MStream m a -> MStream m a) -> v (PrimState m) a -> m (v (PrimState m) a)Source

unstreamR :: (PrimMonad m, MVector v a) => Stream a -> m (v (PrimState m) a)Source

Create a new mutable vector and fill it with elements from the Stream. The vector will grow logarithmically if the Size hint of the Stream is inexact.

transformR :: (PrimMonad m, MVector v a) => (MStream m a -> MStream m a) -> v (PrimState m) a -> m (v (PrimState m) a)Source

unsafeAccum :: (PrimMonad m, MVector v a) => (a -> b -> a) -> v (PrimState m) a -> Stream (Int, b) -> m ()Source

accum :: (PrimMonad m, MVector v a) => (a -> b -> a) -> v (PrimState m) a -> Stream (Int, b) -> m ()Source

unsafeUpdate :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Stream (Int, a) -> m ()Source

update :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Stream (Int, a) -> m ()Source

reverse :: (PrimMonad m, MVector v a) => v (PrimState m) a -> m ()Source

unstablePartition :: forall m v a. (PrimMonad m, MVector v a) => (a -> Bool) -> v (PrimState m) a -> m IntSource

unstablePartitionStream :: (PrimMonad m, MVector v a) => (a -> Bool) -> Stream a -> m (v (PrimState m) a, v (PrimState m) a)Source

partitionStream :: (PrimMonad m, MVector v a) => (a -> Bool) -> Stream a -> m (v (PrimState m) a, v (PrimState m) a)Source