Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- class Arity n where
- arity :: Arity n => n -> Int
- type family Mutable (v :: * -> *) :: * -> * -> *
- type family DimM (v :: * -> * -> *) :: *
- class Arity (DimM v) => MVector v a where
- lengthM :: forall v s a. Arity (DimM v) => v s a -> Int
- 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 ()
- clone :: (PrimMonad m, MVector v a) => v (PrimState m) a -> m (v (PrimState m) a)
- class (Dim v ~ DimM (Mutable v), MVector (Mutable v) a) => IVector v a where
- index :: IVector v a => v a -> Int -> a
- lengthI :: IVector v a => v a -> Int
- 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)
- constructVec :: forall v a. (Arity (Dim v), IVector v a) => Fun (Dim v) a (v a)
- inspectVec :: forall v a b. (Arity (Dim v), IVector v a) => v a -> Fun (Dim v) a b -> b
Mutable vectors
Type class for handling n-ary functions.
type family Mutable (v :: * -> *) :: * -> * -> * Source #
Mutable counterpart of fixed-length vector.
class Arity (DimM v) => MVector v a where Source #
Type class for mutable vectors.
overlaps, copy, move, new, unsafeRead, unsafeWrite
overlaps :: v s a -> v s a -> Bool Source #
Checks whether vectors' buffers overlaps
copy :: PrimMonad m => v (PrimState m) a -> v (PrimState m) a -> m () Source #
Copy vector. The two vectors may not overlap. Since vectors' length is encoded in the type there is no need in runtime checks.
move :: PrimMonad m => v (PrimState m) a -> v (PrimState m) a -> m () Source #
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 a Source #
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.
lengthM :: forall v s a. Arity (DimM v) => v s a -> Int Source #
Length of mutable vector. Function doesn't evaluate its argument.
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.
clone :: (PrimMonad m, MVector v a) => v (PrimState m) a -> m (v (PrimState m) a) Source #
Create copy of vector.
Immutable vectors
class (Dim v ~ DimM (Mutable v), MVector (Mutable v) a) => IVector v a where Source #
Type class for immutable vectors
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 -> a Source #
Get element at specified index without bounds check.
lengthI :: IVector v a => v a -> Int Source #
Length of immutable vector. Function doesn't evaluate its argument.
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.