PrimitiveArray-0.10.1.0: Efficient multidimensional arrays
Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Class

Description

Vastly extended primitive arrays. Some basic ideas are now modeled after the vector package, especially the monadic mutable / pure immutable array system.

Note that in general only bulk operations should error out, error handling for indexreadwrite is too costly. General usage should be to create data structures and run the DP code within an error monad, but keep error handling to high-level operations.

Synopsis

Documentation

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

Mutable version of an array.

Instances

Instances details
(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)
data MutArr m (Sparse w v sh e) Source #

Currently, our mutable variant of sparse matrices will keep indices and manhattan starts immutable as well.

Instance details

Defined in Data.PrimitiveArray.Sparse.BinSearch

data MutArr m (Sparse w v sh e) Source #

Currently, our mutable variant of sparse matrices will keep indices and manhattan starts immutable as well.

Instance details

Defined in Data.PrimitiveArray.Sparse.IntBinSearch

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.1.0-8LhqXNFuZNc70s43xh6tNJ" '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 family FillStruc arr :: * Source #

Associate a fill structure with each type of array (dense, sparse, ...).

Example: type instance FillStruc (Sparse w v sh e) = (w sh) associates the type (w sh), which is of the same type as the underlying w structure holding index information for a sparse array.

Instances

Instances details
type FillStruc (Sparse w v sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Sparse.BinSearch

type FillStruc (Sparse w v sh e) = w sh
type FillStruc (Sparse w v sh e) Source # 
Instance details

Defined in Data.PrimitiveArray.Sparse.IntBinSearch

type FillStruc (Sparse w v sh e) = w sh

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

The core set of operations for pure and monadic arrays.

Methods

upperBound :: arr sh elm -> LimitType sh Source #

Returns the bounds of an immutable array, again inclusive bounds: [lb..ub] .

unsafeIndex :: arr sh elm -> sh -> elm Source #

Extract a single element from the array. Generally unsafe as not bounds-checking is performed.

safeIndex :: arr sh elm -> sh -> Maybe elm Source #

Index into immutable array, but safe in case sh is not part of the array.

transformShape :: Index sh' => (LimitType sh -> LimitType sh') -> arr sh elm -> arr sh' elm Source #

Savely transform the shape space of a table.

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

Return the bounds of the array. All bounds are inclusive, as in [lb..ub]. Technically not monadic, but rather working on a monadic array.

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.

newSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (arr sh elm) -> m (MutArr m (arr sh elm)) Source #

Variant of newM that requires a fill structure. Mostly for special / sparse structures (hence the S, also to be interpreted as "safe", since these functions won't fail with sparse structures).

newWithM :: PrimMonad m => LimitType sh -> elm -> m (MutArr m (arr sh elm)) Source #

Creates a new array with all elements being equal to elm.

newWithSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (arr sh elm) -> elm -> m (MutArr m (arr sh elm)) Source #

Variant of newWithM

readM :: PrimMonad m => MutArr m (arr sh elm) -> sh -> m elm Source #

Reads a single element in the array.

safeReadM :: (Monad m, PrimMonad m) => MutArr m (arr sh elm) -> sh -> m (Maybe elm) Source #

Read from the mutable array, but return Nothing in case sh does not exist. This will allow streaming DP combinators to "jump" over missing elements.

Should be used with Stream.Monadic.mapMaybe to get efficient code.

writeM :: PrimMonad m => MutArr m (arr sh elm) -> sh -> elm -> m () Source #

Writes a single element in the array.

safeWriteM :: (Monad m, PrimMonad m) => MutArr m (arr sh elm) -> sh -> elm -> m () Source #

Write into the mutable array, but if the index sh does not exist, silently continue.

unsafeFreezeM :: 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.

unsafeThawM :: PrimMonad m => arr sh elm -> m (MutArr m (arr sh elm)) Source #

Thaw an immutable array into a mutable one. Both versions share memory.

Instances

Instances details
(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 #

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

safeIndex :: Dense v sh e -> sh -> Maybe e Source #

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

upperBoundM :: forall (m :: Type -> Type). 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 #

newSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (Dense v sh e) -> m (MutArr m (Dense v sh e)) Source #

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

newWithSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (Dense v sh e) -> e -> m (MutArr m (Dense v sh e)) Source #

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

safeReadM :: (Monad m, PrimMonad m) => MutArr m (Dense v sh e) -> sh -> m (Maybe e) Source #

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

safeWriteM :: (Monad m, PrimMonad m) => MutArr m (Dense v sh e) -> sh -> e -> m () Source #

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

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

(Index sh, SparseBucket sh, Eq sh, Ord sh, Vector w sh, Vector w (Int, sh), Vector w (Int, (Int, sh)), Vector v e) => PrimArrayOps (Sparse w v) sh e Source # 
Instance details

Defined in Data.PrimitiveArray.Sparse.BinSearch

Methods

upperBound :: Sparse w v sh e -> LimitType sh Source #

unsafeIndex :: Sparse w v sh e -> sh -> e Source #

safeIndex :: Sparse w v sh e -> sh -> Maybe e Source #

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

upperBoundM :: forall (m :: Type -> Type). MutArr m (Sparse w v sh e) -> LimitType sh Source #

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

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

newSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (Sparse w v sh e) -> m (MutArr m (Sparse w v sh e)) Source #

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

newWithSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (Sparse w v sh e) -> e -> m (MutArr m (Sparse w v sh e)) Source #

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

safeReadM :: (Monad m, PrimMonad m) => MutArr m (Sparse w v sh e) -> sh -> m (Maybe e) Source #

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

safeWriteM :: (Monad m, PrimMonad m) => MutArr m (Sparse w v sh e) -> sh -> e -> m () Source #

unsafeFreezeM :: PrimMonad m => MutArr m (Sparse w v sh e) -> m (Sparse w v sh e) Source #

unsafeThawM :: PrimMonad m => Sparse w v sh e -> m (MutArr m (Sparse w v sh e)) Source #

(Index sh, SparseBucket sh, Eq sh, Ord sh, Vector w sh, Vector w (Int, sh), Vector w (Int, (Int, sh)), Vector w (Int, Int), Vector w Int, Vector v e) => PrimArrayOps (Sparse w v) sh e Source # 
Instance details

Defined in Data.PrimitiveArray.Sparse.IntBinSearch

Methods

upperBound :: Sparse w v sh e -> LimitType sh Source #

unsafeIndex :: Sparse w v sh e -> sh -> e Source #

safeIndex :: Sparse w v sh e -> sh -> Maybe e Source #

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

upperBoundM :: forall (m :: Type -> Type). MutArr m (Sparse w v sh e) -> LimitType sh Source #

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

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

newSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (Sparse w v sh e) -> m (MutArr m (Sparse w v sh e)) Source #

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

newWithSM :: (Monad m, PrimMonad m) => LimitType sh -> FillStruc (Sparse w v sh e) -> e -> m (MutArr m (Sparse w v sh e)) Source #

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

safeReadM :: (Monad m, PrimMonad m) => MutArr m (Sparse w v sh e) -> sh -> m (Maybe e) Source #

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

safeWriteM :: (Monad m, PrimMonad m) => MutArr m (Sparse w v sh e) -> sh -> e -> m () Source #

unsafeFreezeM :: PrimMonad m => MutArr m (Sparse w v sh e) -> m (Sparse w v sh e) Source #

unsafeThawM :: PrimMonad m => Sparse w v sh e -> m (MutArr m (Sparse w v sh e)) Source #

class PrimArrayMap arr sh e e' where Source #

Methods

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

Instances

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

Defined in Data.PrimitiveArray.Dense

Methods

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

(Index sh, Vector v e, Vector v e') => PrimArrayMap (Sparse w v :: Type -> Type -> Type) (sh :: Type) e e' Source # 
Instance details

Defined in Data.PrimitiveArray.Sparse.IntBinSearch

Methods

mapArray :: (e -> e') -> Sparse w v sh e -> Sparse w v sh e' Source #

data PAErrors Source #

Sum type of errors that can happen when using primitive arrays.

Constructors

PAEUpperBound 

Instances

Instances details
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.1.0-8LhqXNFuZNc70s43xh6tNJ" '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.

(!) is rewritten from phase [1] onwards into an optimized form. Before, it uses a very slow form, that does bounds checking.

(!?) :: PrimArrayOps arr sh elm => arr sh elm -> sh -> Maybe elm Source #

Return value at an index that might not exist.

inBoundsM :: (Monad m, PrimArrayOps arr sh elm) => MutArr m (arr sh elm) -> sh -> Bool Source #

Returns true if the index is valid for the array.

fromAssocsM :: (PrimMonad m, PrimArrayOps 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, PrimArrayOps arr sh elm) => LimitType sh -> elm -> m (arr sh elm) Source #

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

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

Initialize an immutable array with a fill structure.

safeNewWithPA :: forall m arr sh elm. (PrimMonad m, MonadError PAErrors m, 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 => 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 => 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.