Safe Haskell | None |
---|---|
Language | Haskell2010 |
Vastly extended primitive arrays. Some basic ideas are now modeled after the vector package, especially the monadic mutable / pure immutable array system.
NOTE all operations in MPrimArrayOps and PrimArrayOps are highly unsafe. No bounds-checking is performed at all.
- data family MutArr (m :: * -> *) (arr :: *) :: *
- class Index sh => MPrimArrayOps arr sh elm where
- class Index sh => PrimArrayOps arr sh elm where
- class Index sh => PrimArrayMap arr sh e e' where
- (!) :: PrimArrayOps arr sh elm => arr sh elm -> sh -> elm
- inBoundsM :: (Monad m, MPrimArrayOps arr sh elm) => MutArr m (arr sh elm) -> sh -> Bool
- fromAssocsM :: (PrimMonad m, MPrimArrayOps arr sh elm) => sh -> sh -> elm -> [(sh, elm)] -> m (MutArr m (arr sh elm))
- assocs :: (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [(sh, elm)]
- fromList :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => sh -> sh -> [elm] -> arr sh elm
- fromAssocs :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => sh -> sh -> elm -> [(sh, elm)] -> arr sh elm
- toList :: (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [elm]
- class FreezeTables m t where
Documentation
data family MutArr (m :: * -> *) (arr :: *) :: * Source #
Mutable version of an array.
(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m ((:.) ts (MutArr m (arr sh elm))) Source # | |
(WriteCell m cs sh, Monad m, MPrimArrayOps arr sh a, PrimMonad m) => WriteCell m ((:.) cs (MutArr m (arr sh a), sh -> m a)) sh Source # | |
Generic (MutArr m (Boxed sh e)) # | |
Generic (MutArr m (Unboxed sh e)) # | |
NFData sh => NFData (MutArr m (Boxed sh e)) # | |
NFData sh => NFData (MutArr m (Unboxed sh e)) # | |
data MutArr m (Boxed sh e) Source # | |
data MutArr m (Unboxed sh e) Source # | |
type Rep (MutArr m (Boxed sh e)) # | |
type Rep (MutArr m (Unboxed sh e)) # | |
type Frozen ((:.) ts (MutArr m (arr sh elm))) Source # | |
class Index sh => MPrimArrayOps arr sh elm where Source #
The core set of operations for monadic arrays.
boundsM :: MutArr m (arr sh elm) -> (sh, sh) Source #
Return the bounds of the array. All bounds are inclusive, as in
[lb..ub]
fromListM :: PrimMonad m => sh -> sh -> [elm] -> m (MutArr m (arr sh elm)) Source #
Given lower and upper bounds and a list of all elements, produce a mutable array.
newM :: PrimMonad m => sh -> sh -> m (MutArr m (arr sh elm)) Source #
Creates a new array with the given bounds with each element within the array being in an undefined state.
newWithM :: PrimMonad m => sh -> sh -> elm -> m (MutArr m (arr sh elm)) Source #
Creates a new array with all elements being equal to elm
.
readM :: PrimMonad m => MutArr m (arr sh elm) -> sh -> m elm Source #
Reads a single element in the array.
writeM :: PrimMonad m => MutArr m (arr sh elm) -> sh -> elm -> m () Source #
Writes a single element in the array.
class Index sh => PrimArrayOps arr sh elm where Source #
The core set of functions on immutable arrays.
bounds :: arr sh elm -> (sh, sh) Source #
Returns the bounds of an immutable array, again inclusive bounds: [lb..ub]
.
unsafeFreeze :: PrimMonad m => MutArr m (arr sh elm) -> m (arr sh elm) Source #
Freezes a mutable array an returns its immutable version. This operation is O(1) and both arrays share the same memory. Do not use the mutable array afterwards.
unsafeThaw :: PrimMonad m => arr sh elm -> m (MutArr m (arr sh elm)) Source #
Thaw an immutable array into a mutable one. Both versions share memory.
unsafeIndex :: arr sh elm -> sh -> elm Source #
Extract a single element from the array. Generally unsafe as not bounds-checking is performed.
transformShape :: Index sh' => (sh -> sh') -> arr sh elm -> arr sh' elm Source #
Savely transform the shape space of a table.
class Index sh => PrimArrayMap arr sh e e' where Source #
(!) :: PrimArrayOps arr sh elm => arr sh elm -> sh -> elm Source #
Infix index operator. Performs minimal bounds-checking using assert in non-optimized code.
inBoundsM :: (Monad m, MPrimArrayOps arr sh elm) => MutArr m (arr sh elm) -> sh -> Bool Source #
Returns true if the index is valid for the array.
fromAssocsM :: (PrimMonad m, MPrimArrayOps arr sh elm) => sh -> sh -> elm -> [(sh, elm)] -> m (MutArr m (arr sh elm)) Source #
Construct a mutable primitive array from a lower and an upper bound, a default element, and a list of associations.
assocs :: (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [(sh, elm)] Source #
Return all associations from an array.
fromList :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => sh -> sh -> [elm] -> arr sh elm Source #
Creates an immutable array from lower and upper bounds and a complete list of elements.
fromAssocs :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => sh -> sh -> elm -> [(sh, elm)] -> arr sh elm Source #
Creates an immutable array from lower and upper bounds, a default element, and a list of associations.
toList :: (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [elm] Source #
Returns all elements of an immutable array as a list.
Freeze an inductive stack of tables with a Z
at the bottom.
class FreezeTables m t where Source #
freezeTables
freezes a stack of tables.
freezeTables :: t -> m (Frozen t) Source #
Applicative m => FreezeTables m Z Source # | |
(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m ((:.) ts (MutArr m (arr sh elm))) Source # | |