vector-0.6: Efficient Arrays

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

Data.Vector.Generic.Base

Description

Class of pure vectors

Synopsis

Documentation

class MVector (Mutable v) a => Vector v a whereSource

Class of immutable vectors.

Methods

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

Unsafely convert a mutable vector to its immutable version without copying. The mutable vector may not be used after this operation.

basicLength :: v a -> IntSource

Length of the vector (not fusible!)

basicUnsafeSlice :: Int -> Int -> v a -> v aSource

Yield a part of the vector without copying it. No range checks!

basicUnsafeIndexM :: Monad m => v a -> Int -> m aSource

Yield the element at the given position in a monad. The monad allows us to be strict in the vector if we want. Suppose we had

 unsafeIndex :: v a -> Int -> a

instead. Now, if we wanted to copy a vector, we'd do something like

 copy mv v ... = ... unsafeWrite mv i (unsafeIndex v i) ...

For lazy vectors, the indexing would not be evaluated which means that we would retain a reference to the original vector in each element we write. This is not what we want!

With basicUnsafeIndexM, we can do

 copy mv v ... = ... case basicUnsafeIndexM v i of
                       Box x -> unsafeWrite mv i x ...

which does not have this problem because indexing (but not the returned element!) is evaluated immediately.

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

Copy an immutable vector into a mutable one.

elemseq :: v a -> a -> b -> bSource

type family Mutable v :: * -> * -> *Source

Mutable v s a is the mutable version of the pure vector type v a with the state token s