Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Vector.Fixed.Mutable
Description
Type classes for vectors which are implemented on top of the arrays
and support in-place mutation. API is similar to one used in the
vector
package.
Synopsis
- type Arity (n :: Nat) = ArityPeano (Peano n)
- type family Mutable (v :: Type -> Type) :: Type -> Type -> Type
- type family DimM (v :: Type -> Type -> Type) :: PeanoNum
- class ArityPeano (DimM v) => MVector (v :: Type -> Type -> Type) a where
- basicCopy :: v s a -> v s a -> ST s ()
- basicNew :: ST s (v s a)
- basicReplicate :: a -> ST s (v s a)
- basicClone :: v s a -> ST s (v s a)
- basicUnsafeRead :: v s a -> Int -> ST s a
- basicUnsafeWrite :: v s a -> Int -> a -> ST s ()
- lengthM :: ArityPeano (DimM v) => v s a -> Int
- new :: (MVector v a, PrimMonad m) => m (v (PrimState m) a)
- clone :: (PrimMonad m, MVector v a) => v (PrimState m) a -> m (v (PrimState m) a)
- copy :: (MVector v a, PrimMonad m) => v (PrimState m) a -> v (PrimState m) a -> m ()
- read :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m a
- write :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> a -> m ()
- unsafeRead :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> m a
- unsafeWrite :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> a -> m ()
- replicate :: (PrimMonad m, MVector v a) => a -> m (v (PrimState m) a)
- replicateM :: (PrimMonad m, MVector v a) => m a -> m (v (PrimState m) a)
- generate :: (PrimMonad m, MVector v a) => (Int -> a) -> m (v (PrimState m) a)
- generateM :: (PrimMonad m, MVector v a) => (Int -> m a) -> m (v (PrimState m) a)
- forI :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (Int -> m ()) -> m ()
- class (Dim v ~ DimM (Mutable v), MVector (Mutable v) a) => IVector (v :: Type -> Type) a where
- basicUnsafeFreeze :: Mutable v s a -> ST s (v a)
- basicThaw :: v a -> ST s (Mutable v s a)
- unsafeIndex :: v a -> Int -> a
- index :: IVector v a => v a -> Int -> a
- freeze :: (PrimMonad m, IVector v a) => Mutable v (PrimState m) a -> m (v a)
- thaw :: (PrimMonad m, IVector v a) => v a -> m (Mutable v (PrimState m) a)
- unsafeFreeze :: (IVector v a, PrimMonad m) => Mutable v (PrimState m) a -> m (v a)
- constructVec :: (ArityPeano (Dim v), IVector v a) => Fun (Dim v) a (v a)
- inspectVec :: (ArityPeano (Dim v), IVector v a) => v a -> Fun (Dim v) a b -> b
Mutable vectors
type Arity (n :: Nat) = ArityPeano (Peano n) Source #
Synonym for writing constrains using type level naturals.
type family Mutable (v :: Type -> Type) :: Type -> Type -> Type Source #
Mutable counterpart of fixed-length vector.
Instances
type Mutable (Vec n) Source # | |
Defined in Data.Vector.Fixed.Boxed | |
type Mutable (Vec n) Source # | |
Defined in Data.Vector.Fixed.Primitive | |
type Mutable (Vec n) Source # | |
Defined in Data.Vector.Fixed.Storable | |
type Mutable (Vec n) Source # | |
Defined in Data.Vector.Fixed.Strict |
type family DimM (v :: Type -> Type -> Type) :: PeanoNum Source #
Dimension for mutable vector.
Instances
type DimM (MVec n) Source # | |
Defined in Data.Vector.Fixed.Boxed | |
type DimM (MVec n) Source # | |
Defined in Data.Vector.Fixed.Primitive | |
type DimM (MVec n) Source # | |
Defined in Data.Vector.Fixed.Storable | |
type DimM (MVec n) Source # | |
Defined in Data.Vector.Fixed.Strict |
class ArityPeano (DimM v) => MVector (v :: Type -> Type -> Type) a where Source #
Type class for mutable vectors.
Minimal complete definition
Methods
Arguments
:: v s a | Target |
-> v s a | Source |
-> ST s () |
Copy vector. The two vectors may not overlap. Shouldn't be used
directly, use copy
instead.
basicNew :: ST s (v s a) Source #
Allocate new uninitialized vector. Shouldn't be used
directly, use new
instead.
basicReplicate :: a -> ST s (v s a) Source #
Allocate new vector initialized with given element. Shouldn't be used
directly, use replicate
instead.
basicClone :: v s a -> ST s (v s a) Source #
Create copy of existing vector. Shouldn't be used
directly, use clone
instead.
basicUnsafeRead :: v s a -> Int -> ST s a Source #
Read value at index without bound checks. Shouldn't be used
directly, use unsafeRead
instead.
basicUnsafeWrite :: v s a -> Int -> a -> ST s () Source #
Write value at index without bound checks. Shouldn't be used
directly, use unsafeWrite
instead.
Instances
lengthM :: ArityPeano (DimM v) => v s a -> Int Source #
Length of mutable vector. Function doesn't evaluate its argument.
new :: (MVector v a, PrimMonad m) => m (v (PrimState m) a) Source #
Create new uninitialized mutable vector.
clone :: (PrimMonad m, MVector v a) => v (PrimState m) a -> m (v (PrimState m) a) Source #
Create copy of vector.
Examples:
>>>
import Control.Monad.ST (runST)
>>>
import Data.Vector.Fixed (mk3)
>>>
import Data.Vector.Fixed.Boxed (Vec3)
>>>
import qualified Data.Vector.Fixed.Mutable as M
>>>
let x = runST (do { v <- M.replicate 100; v' <- clone v; M.write v' 0 2; M.unsafeFreeze v' }) :: Vec3 Int
>>>
x
[2,100,100]
Copy vector. The two vectors may not overlap. Since vectors' length is encoded in the type there is no need in runtime checks of length.
read :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m a Source #
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.
unsafeRead :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> m a Source #
Read value at index without bound checks.
unsafeWrite :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> a -> m () Source #
Write value at index without bound checks.
Creation
replicate :: (PrimMonad m, MVector v a) => a -> m (v (PrimState m) a) Source #
Create new vector with all elements set to given value.
replicateM :: (PrimMonad m, MVector v a) => m a -> m (v (PrimState m) a) Source #
Create new vector with all elements are generated by provided monadic action.
generate :: (PrimMonad m, MVector v a) => (Int -> a) -> m (v (PrimState m) a) Source #
Create new vector with using function from index to value.
generateM :: (PrimMonad m, MVector v a) => (Int -> m a) -> m (v (PrimState m) a) Source #
Create new vector with using monadic function from index to value.
Loops
forI :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (Int -> m ()) -> m () Source #
Loop which calls function for each index
Immutable vectors
class (Dim v ~ DimM (Mutable v), MVector (Mutable v) a) => IVector (v :: Type -> Type) a where Source #
Type class for immutable vectors
Methods
basicUnsafeFreeze :: Mutable v s a -> ST s (v a) Source #
Convert vector to immutable state. Mutable vector must not be modified afterwards.
basicThaw :: v a -> ST s (Mutable v s a) Source #
Convert immutable vector to mutable by copying it.
unsafeIndex :: v a -> Int -> a Source #
Get element at specified index without bounds check.
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.
unsafeFreeze :: (IVector v a, PrimMonad m) => Mutable v (PrimState m) a -> m (v a) Source #
Convert vector to immutable state. Mutable vector must not be modified afterwards.
Vector API
constructVec :: (ArityPeano (Dim v), IVector v a) => Fun (Dim v) a (v a) Source #
Generic construct implementation for array-based vectors.
inspectVec :: (ArityPeano (Dim v), IVector v a) => v a -> Fun (Dim v) a b -> b Source #
Generic inspect implementation for array-based vectors.