vector-0.6: Efficient Arrays

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

Data.Vector.Primitive.Mutable

Contents

Description

Mutable primitive vectors.

Synopsis

Mutable vectors of primitive types

data MVector s a Source

Mutable vectors of primitive types.

Constructors

MVector !Int !Int !(MutableByteArray s) 

Instances

class Prim a

Class of types supporting primitive array operations

Operations on mutable vectors

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

Length of the mutable vector.

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

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

Yield a part of the mutable vector without copying it.

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

Create a mutable vector of the given length.

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

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

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

Yield the element at the given position.

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

Replace the element at the given position.

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

Swap the elements at the given positions.

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

Set all elements of the vector to the given value.

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

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

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

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

Unsafe operations

unsafeSliceSource

Arguments

:: Prim a 
=> Int

starting index

-> Int

length of the slice

-> MVector s a 
-> MVector s a 

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

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

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

unsafeNewWith :: (PrimMonad m, Prim a) => Int -> a -> m (MVector (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, Prim a) => MVector (PrimState m) a -> Int -> m aSource

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

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

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

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

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

unsafeCopySource

Arguments

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

target

-> MVector (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, Prim a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)Source

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