raw-feldspar-0.3: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Data.Storable

Contents

Description

Storable types

Note that the Storable interface is currently not ideal for vectors:

  • The Store representation only allows a vector to be read back as the same type as it was written. But it is usually desired to read a vector as Manifest regardless of what type it was written as.

  • There is no support for double-buffered storage, as provided by Feldspar.Data.Buffered which means that memory management can become more tedious.
Synopsis

Forcible class

class Forcible a where Source #

Expression types that can be "forced" to values

Associated Types

type ValueRep a Source #

Representation of a forced value

Methods

toValue :: MonadComp m => a -> m (ValueRep a) Source #

Force an expression to a value. The resulting value can be used multiple times without risking re-computation.

toValue will allocate memory to hold the value.

fromValue :: ValueRep a -> a Source #

Convert a forced value back to an expression

Instances
Forcible a => Forcible [a] Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep [a] :: Type Source #

Methods

toValue :: MonadComp m => [a] -> m (ValueRep [a]) Source #

fromValue :: ValueRep [a] -> [a] Source #

Type a => Forcible (Data a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep (Data a) :: Type Source #

Methods

toValue :: MonadComp m => Data a -> m (ValueRep (Data a)) Source #

fromValue :: ValueRep (Data a) -> Data a Source #

Forcible a => Forcible (Validated a) Source #

toValue will force the value even if it's invalid

Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep (Validated a) :: Type Source #

Syntax a => Forcible (Option a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep (Option a) :: Type Source #

(Forcible a, Forcible b) => Forcible (a, b) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep (a, b) :: Type Source #

Methods

toValue :: MonadComp m => (a, b) -> m (ValueRep (a, b)) Source #

fromValue :: ValueRep (a, b) -> (a, b) Source #

(Forcible a, Forcible b, Forcible c) => Forcible (a, b, c) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep (a, b, c) :: Type Source #

Methods

toValue :: MonadComp m => (a, b, c) -> m (ValueRep (a, b, c)) Source #

fromValue :: ValueRep (a, b, c) -> (a, b, c) Source #

(Forcible a, Forcible b, Forcible c, Forcible d) => Forcible (a, b, c, d) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type ValueRep (a, b, c, d) :: Type Source #

Methods

toValue :: MonadComp m => (a, b, c, d) -> m (ValueRep (a, b, c, d)) Source #

fromValue :: ValueRep (a, b, c, d) -> (a, b, c, d) Source #

forceCast :: (Forcible a, Forcible b, ValueRep a ~ ValueRep b, MonadComp m) => a -> m b Source #

Cast between Forcible types that have the same value representation

force :: (Forcible a, MonadComp m) => a -> m a Source #

Force the computation of an expression. The resulting value can be used multiple times without risking re-computation.

Storable class

class Storable a where Source #

Storable types

Associated Types

type StoreRep a Source #

Memory representation

type StoreSize a Source #

Size of memory representation

Methods

newStoreRep :: MonadComp m => proxy a -> StoreSize a -> m (StoreRep a) Source #

Creat a fresh memory store. It is usually better to use newStore instead of this function as it improves type inference.

initStoreRep :: MonadComp m => a -> m (StoreRep a) Source #

Store a value to a fresh memory store. It is usually better to use initStore instead of this function as it improves type inference.

readStoreRep :: MonadComp m => StoreRep a -> m a Source #

Read from a memory store. It is usually better to use readStore instead of this function as it improves type inference.

unsafeFreezeStoreRep :: MonadComp m => StoreRep a -> m a Source #

Unsafe freezing of a memory store. It is usually better to use unsafeFreezeStore instead of this function as it improves type inference.

writeStoreRep :: MonadComp m => StoreRep a -> a -> m () Source #

Write to a memory store. It is usually better to use writeStore instead of this function as it improves type inference.

Instances
Storable () Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep () :: Type Source #

type StoreSize () :: Type Source #

Methods

newStoreRep :: MonadComp m => proxy () -> StoreSize () -> m (StoreRep ()) Source #

initStoreRep :: MonadComp m => () -> m (StoreRep ()) Source #

readStoreRep :: MonadComp m => StoreRep () -> m () Source #

unsafeFreezeStoreRep :: MonadComp m => StoreRep () -> m () Source #

writeStoreRep :: MonadComp m => StoreRep () -> () -> m () Source #

Type a => Storable (Data a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (Data a) :: Type Source #

type StoreSize (Data a) :: Type Source #

Methods

newStoreRep :: MonadComp m => proxy (Data a) -> StoreSize (Data a) -> m (StoreRep (Data a)) Source #

initStoreRep :: MonadComp m => Data a -> m (StoreRep (Data a)) Source #

readStoreRep :: MonadComp m => StoreRep (Data a) -> m (Data a) Source #

unsafeFreezeStoreRep :: MonadComp m => StoreRep (Data a) -> m (Data a) Source #

writeStoreRep :: MonadComp m => StoreRep (Data a) -> Data a -> m () Source #

Syntax a => Storable (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (Pull a) :: Type Source #

type StoreSize (Pull a) :: Type Source #

Methods

newStoreRep :: MonadComp m => proxy (Pull a) -> StoreSize (Pull a) -> m (StoreRep (Pull a)) Source #

initStoreRep :: MonadComp m => Pull a -> m (StoreRep (Pull a)) Source #

readStoreRep :: MonadComp m => StoreRep (Pull a) -> m (Pull a) Source #

unsafeFreezeStoreRep :: MonadComp m => StoreRep (Pull a) -> m (Pull a) Source #

writeStoreRep :: MonadComp m => StoreRep (Pull a) -> Pull a -> m () Source #

Syntax a => Storable (Manifest2 a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (Manifest2 a) :: Type Source #

type StoreSize (Manifest2 a) :: Type Source #

Syntax a => Storable (Manifest a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (Manifest a) :: Type Source #

type StoreSize (Manifest a) :: Type Source #

(Storable a, Syntax a, StoreSize a ~ ()) => Storable (Option a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (Option a) :: Type Source #

type StoreSize (Option a) :: Type Source #

(Storable a, Storable b) => Storable (a, b) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (a, b) :: Type Source #

type StoreSize (a, b) :: Type Source #

Methods

newStoreRep :: MonadComp m => proxy (a, b) -> StoreSize (a, b) -> m (StoreRep (a, b)) Source #

initStoreRep :: MonadComp m => (a, b) -> m (StoreRep (a, b)) Source #

readStoreRep :: MonadComp m => StoreRep (a, b) -> m (a, b) Source #

unsafeFreezeStoreRep :: MonadComp m => StoreRep (a, b) -> m (a, b) Source #

writeStoreRep :: MonadComp m => StoreRep (a, b) -> (a, b) -> m () Source #

Syntax a => Storable (Push Comp a) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (Push Comp a) :: Type Source #

type StoreSize (Push Comp a) :: Type Source #

(Storable a, Storable b, Storable c) => Storable (a, b, c) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (a, b, c) :: Type Source #

type StoreSize (a, b, c) :: Type Source #

Methods

newStoreRep :: MonadComp m => proxy (a, b, c) -> StoreSize (a, b, c) -> m (StoreRep (a, b, c)) Source #

initStoreRep :: MonadComp m => (a, b, c) -> m (StoreRep (a, b, c)) Source #

readStoreRep :: MonadComp m => StoreRep (a, b, c) -> m (a, b, c) Source #

unsafeFreezeStoreRep :: MonadComp m => StoreRep (a, b, c) -> m (a, b, c) Source #

writeStoreRep :: MonadComp m => StoreRep (a, b, c) -> (a, b, c) -> m () Source #

(Storable a, Storable b, Storable c, Storable d) => Storable (a, b, c, d) Source # 
Instance details

Defined in Feldspar.Data.Storable

Associated Types

type StoreRep (a, b, c, d) :: Type Source #

type StoreSize (a, b, c, d) :: Type Source #

Methods

newStoreRep :: MonadComp m => proxy (a, b, c, d) -> StoreSize (a, b, c, d) -> m (StoreRep (a, b, c, d)) Source #

initStoreRep :: MonadComp m => (a, b, c, d) -> m (StoreRep (a, b, c, d)) Source #

readStoreRep :: MonadComp m => StoreRep (a, b, c, d) -> m (a, b, c, d) Source #

unsafeFreezeStoreRep :: MonadComp m => StoreRep (a, b, c, d) -> m (a, b, c, d) Source #

writeStoreRep :: MonadComp m => StoreRep (a, b, c, d) -> (a, b, c, d) -> m () Source #

initStoreRepVec :: forall m vec. (Storable vec, StoreSize vec ~ Data Length, Finite vec, MonadComp m) => vec -> m (StoreRep vec) Source #

initStoreRepVec2 :: forall m vec. (Storable vec, StoreSize vec ~ (Data Length, Data Length), Finite2 vec, MonadComp m) => vec -> m (StoreRep vec) Source #

writeStoreRepVec :: (Manifestable m vec a, StoreRep vec ~ (DRef Length, Arr a), Finite vec, Syntax a, MonadComp m) => StoreRep vec -> vec -> m () Source #

writeStoreRepVec2 :: (Manifestable2 m vec a, StoreRep vec ~ (DRef Length, DRef Length, Arr a), Finite2 vec, Syntax a, MonadComp m) => StoreRep vec -> vec -> m () Source #

User interface

newtype Store a Source #

Memory for storing values

Constructors

Store 

Fields

newStore :: forall a m. (Storable a, MonadComp m) => StoreSize a -> m (Store a) Source #

Create a fresh Store

initStore :: (Storable a, MonadComp m) => a -> m (Store a) Source #

Store a value to a fresh Store

readStore :: (Storable a, MonadComp m) => Store a -> m a Source #

Read from a Store

unsafeFreezeStore :: (Storable a, MonadComp m) => Store a -> m a Source #

Unsafe freezeing of a Store. This operation is only safe if the Store is not updated as long as the resulting value is alive.

writeStore :: (Storable a, MonadComp m) => Store a -> a -> m () Source #

Write to a Store

inplace :: (Storable a, MonadComp m) => Store a -> (a -> a) -> m () Source #

Update a Store in-place