PrimitiveArray-0.8.0.1: 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 # 

Associated Types

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

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (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 # 

Methods

unsafeWriteCell :: (cs :. (MutArr m (arr sh a), sh -> m a)) -> sh -> m () Source #

writeCell :: (cs :. (MutArr m (arr sh a), sh -> m a)) -> sh -> m () Source #

Generic (MutArr m (Boxed sh e)) # 

Associated Types

type Rep (MutArr m (Boxed sh e)) :: * -> * #

Methods

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

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

Generic (MutArr m (Unboxed sh e)) # 

Associated Types

type Rep (MutArr m (Unboxed sh e)) :: * -> * #

Methods

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

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

NFData sh => NFData (MutArr m (Boxed sh e)) # 

Methods

rnf :: MutArr m (Boxed sh e) -> () #

NFData sh => NFData (MutArr m (Unboxed sh e)) # 

Methods

rnf :: MutArr m (Unboxed sh e) -> () #

data MutArr m (Boxed sh e) Source # 
data MutArr m (Boxed sh e) = MBoxed !sh !sh !(MVector (PrimState m) e)
data MutArr m (Unboxed sh e) Source # 
data MutArr m (Unboxed sh e) = MUnboxed !sh !sh !(MVector (PrimState m) e)
type Rep (MutArr m (Boxed sh e)) # 
type Rep (MutArr m (Boxed sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.8.0.1-H8L9mO6Qdgd6EjLRyswnkq" False) (C1 (MetaCons "MBoxed" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 sh)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 sh)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 (MVector (PrimState m) e))))))
type Rep (MutArr m (Unboxed sh e)) # 
type Rep (MutArr m (Unboxed sh e)) = D1 (MetaData "MutArr" "Data.PrimitiveArray.Dense" "PrimitiveArray-0.8.0.1-H8L9mO6Qdgd6EjLRyswnkq" False) (C1 (MetaCons "MUnboxed" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 sh)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 sh)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MVector (PrimState m) e))))))
type Frozen ((:.) ts (MutArr m (arr sh elm))) Source # 
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.

Minimal complete definition

boundsM, fromListM, newM, newWithM, readM, writeM

Methods

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.

Instances

Index sh => MPrimArrayOps Boxed sh elm Source # 

Methods

boundsM :: MutArr m (Boxed sh elm) -> (sh, sh) Source #

fromListM :: PrimMonad m => sh -> sh -> [elm] -> m (MutArr m (Boxed sh elm)) Source #

newM :: PrimMonad m => sh -> sh -> m (MutArr m (Boxed sh elm)) Source #

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

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

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

(Index sh, Unbox elm) => MPrimArrayOps Unboxed sh elm Source # 

Methods

boundsM :: MutArr m (Unboxed sh elm) -> (sh, sh) Source #

fromListM :: PrimMonad m => sh -> sh -> [elm] -> m (MutArr m (Unboxed sh elm)) Source #

newM :: PrimMonad m => sh -> sh -> m (MutArr m (Unboxed sh elm)) Source #

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

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

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

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

The core set of functions on immutable arrays.

Methods

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.

Instances

Index sh => PrimArrayOps Boxed sh elm Source # 

Methods

bounds :: Boxed sh elm -> (sh, sh) Source #

unsafeFreeze :: PrimMonad m => MutArr m (Boxed sh elm) -> m (Boxed sh elm) Source #

unsafeThaw :: PrimMonad m => Boxed sh elm -> m (MutArr m (Boxed sh elm)) Source #

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

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

(Index sh, Unbox elm) => PrimArrayOps Unboxed sh elm Source # 

Methods

bounds :: Unboxed sh elm -> (sh, sh) Source #

unsafeFreeze :: PrimMonad m => MutArr m (Unboxed sh elm) -> m (Unboxed sh elm) Source #

unsafeThaw :: PrimMonad m => Unboxed sh elm -> m (MutArr m (Unboxed sh elm)) Source #

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

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

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

Minimal complete definition

map

Methods

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

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

Instances

Index sh => PrimArrayMap Boxed sh e e' Source # 

Methods

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

(Index sh, Unbox e, Unbox e') => PrimArrayMap Unboxed sh e e' Source # 

Methods

map :: (e -> e') -> Unboxed sh e -> Unboxed sh e' 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.

Minimal complete definition

freezeTables

Associated Types

type Frozen t :: * Source #

Methods

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

Instances

Applicative m => FreezeTables m Z Source # 

Associated Types

type Frozen Z :: * 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 # 

Associated Types

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

Methods

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