PrimitiveArray-0.10.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Class

Contents

Description

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.

Synopsis

Documentation

data family MutArr (m :: * -> *) (arr :: *) :: * Source #

Mutable version of an array.

Instances
(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen (ts :. MutArr m (arr sh elm)) :: Type Source #

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (ts :. MutArr m (arr sh elm))) Source #

(Show (LimitType sh), Show (Mutable v (PrimState m) e), Mutable v (PrimState m) e ~ mv) => Show (MutArr m (Dense v sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

showsPrec :: Int -> MutArr m (Dense v sh e) -> ShowS #

show :: MutArr m (Dense v sh e) -> String #

showList :: [MutArr m (Dense v sh e)] -> ShowS #

Generic (MutArr m (Dense v sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Associated Types

type Rep (MutArr m (Dense v sh e)) :: Type -> Type #

Methods

from :: MutArr m (Dense v sh e) -> Rep (MutArr m (Dense v sh e)) x #

to :: Rep (MutArr m (Dense v sh e)) x -> MutArr m (Dense v sh e) #

(NFData (LimitType sh), NFData (Mutable v (PrimState m) e), Mutable v (PrimState m) e ~ mv) => NFData (MutArr m (Dense v sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

rnf :: MutArr m (Dense v sh e) -> () #

data MutArr m (Dense v sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

data MutArr m (Dense v sh e) = MDense !(LimitType sh) !(Mutable v (PrimState m) e)
type Rep (MutArr m (Dense v sh e)) Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

type Rep (MutArr m (Dense v sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.10.0.0-9ZiWRteIvkwDQtOsCN6eid" False) (C1 (MetaCons "MDense" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LimitType sh)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Mutable v (PrimState m) e))))
type Frozen (ts :. MutArr m (arr sh elm)) Source # 
Instance details

Defined in Data.PrimitiveArray.Class

type Frozen (ts :. MutArr m (arr sh elm)) = Frozen ts :. arr sh elm

class Index sh => MPrimArrayOps arr sh elm where Source #

The core set of operations for monadic arrays.

Methods

upperBoundM :: MutArr m (arr sh elm) -> LimitType sh Source #

Return the bounds of the array. All bounds are inclusive, as in [lb..ub]

fromListM :: PrimMonad m => LimitType 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 => LimitType 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 => LimitType 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.

Instances
(Index sh, MutArr m (Dense v sh e) ~ mv, MVector (Mutable v) e) => MPrimArrayOps (Dense v) sh e Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBoundM :: MutArr m (Dense v sh e) -> LimitType sh Source #

fromListM :: PrimMonad m => LimitType sh -> [e] -> m (MutArr m (Dense v sh e)) Source #

newM :: PrimMonad m => LimitType sh -> m (MutArr m (Dense v sh e)) Source #

newWithM :: PrimMonad m => LimitType sh -> e -> m (MutArr m (Dense v sh e)) Source #

readM :: PrimMonad m => MutArr m (Dense v sh e) -> sh -> m e Source #

writeM :: PrimMonad m => MutArr m (Dense v sh e) -> sh -> e -> m () Source #

class Index sh => PrimArrayOps arr sh elm where Source #

The core set of functions on immutable arrays.

Methods

upperBound :: arr sh elm -> LimitType 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' => (LimitType sh -> LimitType sh') -> arr sh elm -> arr sh' elm Source #

Savely transform the shape space of a table.

Instances
(Index sh, Vector v e) => PrimArrayOps (Dense v) sh e Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

upperBound :: Dense v sh e -> LimitType sh Source #

unsafeFreeze :: PrimMonad m => MutArr m (Dense v sh e) -> m (Dense v sh e) Source #

unsafeThaw :: PrimMonad m => Dense v sh e -> m (MutArr m (Dense v sh e)) Source #

unsafeIndex :: Dense v sh e -> sh -> e Source #

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> Dense v sh e -> Dense v sh' e Source #

class Index sh => PrimArrayMap arr sh e e' where Source #

Methods

map :: (e -> e') -> arr sh e -> arr sh e' Source #

Map a function over each element, keeping the shape intact.

Instances
(Index sh, Vector v e, Vector v e') => PrimArrayMap (Dense v) sh e e' Source # 
Instance details

Defined in Data.PrimitiveArray.Dense

Methods

map :: (e -> e') -> Dense v sh e -> Dense v sh e' Source #

data PAErrors Source #

Constructors

PAEUpperBound 
Instances
Eq PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Show PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Generic PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Rep PAErrors :: Type -> Type #

Methods

from :: PAErrors -> Rep PAErrors x #

to :: Rep PAErrors x -> PAErrors #

type Rep PAErrors Source # 
Instance details

Defined in Data.PrimitiveArray.Class

type Rep PAErrors = D1 (MetaData "PAErrors" "Data.PrimitiveArray.Class" "PrimitiveArray-0.10.0.0-9ZiWRteIvkwDQtOsCN6eid" False) (C1 (MetaCons "PAEUpperBound" PrefixI False) (U1 :: Type -> Type))

(!) :: 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) => LimitType 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.

newWithPA :: (PrimMonad m, MPrimArrayOps arr sh elm, PrimArrayOps arr sh elm) => LimitType sh -> elm -> m (arr sh elm) Source #

Initialize an immutable array but stay within the primitive monad m.

safeNewWithPA :: forall m arr sh elm. (PrimMonad m, MonadError PAErrors m, MPrimArrayOps arr sh elm, PrimArrayOps arr sh elm) => LimitType sh -> elm -> m (arr sh elm) Source #

Safely prepare a primitive array.

TODO Check if having a MonadError instance degrades performance. (We should see this once the test with NeedlemanWunsch is under way).

assocs :: forall arr sh elm. (IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> [(sh, elm)] Source #

Return all associations from an array.

assocsS :: forall m arr sh elm. (Monad m, IndexStream sh, PrimArrayOps arr sh elm) => arr sh elm -> Stream m (sh, elm) Source #

Return all associations from an array.

fromList :: (PrimArrayOps arr sh elm, MPrimArrayOps arr sh elm) => LimitType 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) => LimitType 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 :: forall arr sh elm. (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.

Associated Types

type Frozen t :: * Source #

Methods

freezeTables :: t -> m (Frozen t) Source #

Instances
Applicative m => FreezeTables m Z Source # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen Z :: Type Source #

Methods

freezeTables :: Z -> m (Frozen 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 # 
Instance details

Defined in Data.PrimitiveArray.Class

Associated Types

type Frozen (ts :. MutArr m (arr sh elm)) :: Type Source #

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (ts :. MutArr m (arr sh elm))) Source #