| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Feldspar.Data.Storable
Description
Storable types
Note that the Storable interface is currently not ideal for vectors:
The
Storerepresentation 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 asManifestregardless of what type it was written as.- But this is solved by using functions that operated on 
StoreRepinstead (such asreadStoreRep). 
- But this is solved by using functions that operated on 
 - There is no support for double-buffered storage, as provided by Feldspar.Data.Buffered which means that memory management can become more tedious.
 
Synopsis
- class Forcible a where
 - forceCast :: (Forcible a, Forcible b, ValueRep a ~ ValueRep b, MonadComp m) => a -> m b
 - force :: (Forcible a, MonadComp m) => a -> m a
 - class Storable a where
- type StoreRep a
 - type StoreSize a
 - newStoreRep :: MonadComp m => proxy a -> StoreSize a -> m (StoreRep a)
 - initStoreRep :: MonadComp m => a -> m (StoreRep a)
 - readStoreRep :: MonadComp m => StoreRep a -> m a
 - unsafeFreezeStoreRep :: MonadComp m => StoreRep a -> m a
 - writeStoreRep :: MonadComp m => StoreRep a -> a -> m ()
 
 - initStoreRepVec :: forall m vec. (Storable vec, StoreSize vec ~ Data Length, Finite vec, MonadComp m) => vec -> m (StoreRep vec)
 - initStoreRepVec2 :: forall m vec. (Storable vec, StoreSize vec ~ (Data Length, Data Length), Finite2 vec, MonadComp m) => vec -> m (StoreRep vec)
 - writeStoreRepVec :: (Manifestable m vec a, StoreRep vec ~ (DRef Length, Arr a), Finite vec, Syntax a, MonadComp m) => StoreRep vec -> vec -> m ()
 - writeStoreRepVec2 :: (Manifestable2 m vec a, StoreRep vec ~ (DRef Length, DRef Length, Arr a), Finite2 vec, Syntax a, MonadComp m) => StoreRep vec -> vec -> m ()
 - newtype Store a = Store {}
 - newStore :: forall a m. (Storable a, MonadComp m) => StoreSize a -> m (Store a)
 - initStore :: (Storable a, MonadComp m) => a -> m (Store a)
 - readStore :: (Storable a, MonadComp m) => Store a -> m a
 - unsafeFreezeStore :: (Storable a, MonadComp m) => Store a -> m a
 - writeStore :: (Storable a, MonadComp m) => Store a -> a -> m ()
 - inplace :: (Storable a, MonadComp m) => Store a -> (a -> a) -> m ()
 
Forcible class
class Forcible a where Source #
Expression types that can be "forced" to values
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 # | |
| Type a => Forcible (Data a) Source # | |
| Forcible a => Forcible (Validated a) Source # | 
  | 
| Syntax a => Forcible (Option a) Source # | |
| (Forcible a, Forcible b) => Forcible (a, b) Source # | |
| (Forcible a, Forcible b, Forcible c) => Forcible (a, b, c) Source # | |
| (Forcible a, Forcible b, Forcible c, Forcible d) => Forcible (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
Memory representation
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
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
newStore :: forall a m. (Storable a, MonadComp m) => StoreSize a -> m (Store a) Source #
Create a fresh Store