fixed-vector-0.1.2: Generic vectors with fixed length

Safe HaskellNone

Data.Vector.Fixed.Mutable

Contents

Description

Type classes for array based vector. They are quite similar to ones from vector package but those only suitable for vectors with variable length.

Synopsis

Mutable vectors

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

Mutable counterpart of fixed-length vector

type family DimM v :: *Source

Dimension for mutable vector

class Arity (DimM v) => MVector v a whereSource

Type class for mutable vectors

Methods

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

Checks whether vectors' buffers overlaps

copySource

Arguments

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

Target

-> v (PrimState m) a

Source

-> m () 

Copy vector. The two vectors may not overlap. Since vectors' length is encoded in the type there is no need in runtime checks.

moveSource

Arguments

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

Target

-> v (PrimState m) a

Source

-> m () 

Copy vector. The two vectors may overlap. Since vectors' length is encoded in the type there is no need in runtime checks.

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

Allocate new vector

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

Read value at index without bound checks.

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

Write value at index without bound checks.

Instances

(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) a 
(Arity (DimM (MVec n)), Arity n, Prim a) => MVector (MVec n) a 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Double 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Float 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Char 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Word64 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Word32 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Word16 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Word8 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Word 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Int64 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Int32 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Int16 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Int8 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Int 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) Bool 
(Arity (DimM (MVec n)), Arity n) => MVector (MVec n) () 
(Arity (DimM (MVec n)), Arity n, Storable a) => MVector (MVec n) a 
(Arity (DimM (MVec n)), Arity n, MVector (MVec n) a) => MVector (MVec n) (Complex a) 
(Arity (DimM (MVec n)), Arity n, MVector (MVec n) a, MVector (MVec n) b) => MVector (MVec n) (a, b) 
(Arity (DimM (MVec n)), Arity n, MVector (MVec n) a, MVector (MVec n) b, MVector (MVec n) c) => MVector (MVec n) (a, b, c) 

lengthM :: forall v s a. Arity (DimM v) => v s a -> IntSource

Length of mutable vector

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

Read value at index with bound checks.

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

Write value at index with bound checks.

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

Clone vector

Immutable vectors

class (Dim v ~ DimM (Mutable v), MVector (Mutable v) a) => IVector v a whereSource

Type class for immutable vectors

Methods

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

Convert vector to immutable state. Mutable vector must not be modified afterwards.

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

Convert immutable vector to mutable. Immutable vector must not be used afterwards.

unsafeIndex :: v a -> Int -> aSource

Get element at specified index

Instances

(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) a, Arity n) => IVector (Vec n) a 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) a, Arity n, Prim a) => IVector (Vec n) a 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Double, Arity n) => IVector (Vec n) Double 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Float, Arity n) => IVector (Vec n) Float 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Char, Arity n) => IVector (Vec n) Char 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Word64, Arity n) => IVector (Vec n) Word64 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Word32, Arity n) => IVector (Vec n) Word32 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Word16, Arity n) => IVector (Vec n) Word16 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Word8, Arity n) => IVector (Vec n) Word8 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Word, Arity n) => IVector (Vec n) Word 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Int64, Arity n) => IVector (Vec n) Int64 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Int32, Arity n) => IVector (Vec n) Int32 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Int16, Arity n) => IVector (Vec n) Int16 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Int8, Arity n) => IVector (Vec n) Int8 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Int, Arity n) => IVector (Vec n) Int 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) Bool, Arity n) => IVector (Vec n) Bool 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) (), Arity n) => IVector (Vec n) () 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) a, Arity n, Storable a) => IVector (Vec n) a 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) (Complex a), Arity n, IVector (Vec n) a) => IVector (Vec n) (Complex a) 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) (a, b), Arity n, IVector (Vec n) a, IVector (Vec n) b) => IVector (Vec n) (a, b) 
(~ * (Dim (Vec n)) (DimM (Mutable (Vec n))), MVector (Mutable (Vec n)) (a, b, c), Arity n, Vector (Vec n) a, Vector (Vec n) b, Vector (Vec n) c, IVector (Vec n) a, IVector (Vec n) b, IVector (Vec n) c) => IVector (Vec n) (a, b, c) 

index :: IVector v a => v a -> Int -> aSource

lengthI :: IVector v a => v a -> IntSource

Length of immutable vector

freeze :: (PrimMonad m, IVector v a) => Mutable v (PrimState m) a -> m (v a)Source

Safely convert mutable vector to immutable.

thaw :: (PrimMonad m, IVector v a) => v a -> m (Mutable v (PrimState m) a)Source

Safely convert immutable vector to mutable.

Vector API

constructVec :: forall v a. (Arity (Dim v), IVector v a) => Fun (Dim v) a (v a)Source

Generic construct

inspectVec :: forall v a b. (Arity (Dim v), IVector v a) => v a -> Fun (Dim v) a b -> bSource

Generic inspect