raw-feldspar-0.3: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Data.Vector

Contents

Description

This module gives a library of different vector types.

Basic use

A typical 1-dimensional vector computation goes as follows:

  1. Start with a Manifest vector (one that is refers directly to an array in memory).
  2. Apply operations overloaded by Pully (e.g. take, drop, map, reverse). The result is one or more Pull vectors.
  3. If the previous step resulted in several parts, assemble them using operations overloaded by Pushy (e.g. ++). The result is a Push vector.
  4. Write the vector to memory using manifest or manifestFresh.

(Of course, there are many variations on this general scheme.)

Note that it's possible to skip step #2 or #3 above. For example, it's possible to directly concatenate two Manifest vectors using ++, and manifest can be applied directly to a Pull vector (or even to a Manifest, in which case it becomes a no-op).

Efficiency and fusion

The library has been designed so that all operations fuse together without creating any intermediate structures in memory. The only exception is the operations that produce Manifest or Manifest2 vectors (manifest, manifest2, etc.).

For example, the following function only creates a single structure in memory even though it seemingly generates several intermediate vectors:

f :: (Num a, Syntax a, MonadComp m) => Pull a -> m (Manifest a)
f = manifestFresh . reverse . map (*2) . take 10

Furthermore, the operations associated with each type of vector are restricted to operations that can be carried out efficiently for that type. For example, although it would be possible to implement append for Pull vectors, doing so results in unnecessary conditionals in the generated code. Therefore, the ++ operator returns a Push vector, which ensures efficient generated code.

In many cases, the cycle Manifest -> Pull -> Push -> Manifest is guided by the types of the operations involved. However, there are cases when it's preferable to shortcut the cycle even when it's not demanded by the types. The reason is that fusion can lead to duplicated computations.

Here is an example where fusion leads to redundant computations:

bad = do
    v :: DManifest Int32 <- readStd  -- Read from stdin
    let v'  = map heavy v
        v'' = v' ++ reverse v'
    writeStd v''                     -- Write to stdout

Since v' is used twice in defining v'', the mapping of the heavy computation will be done twice when writing v'' to the output. One way to prevent this is to perform the heavy mapping once, store the result in memory, and define v'' from the stored vector:

good = do
    v :: DManifest Int32 <- readStd  -- Read from stdin
    v' <- manifestFresh $ map heavy v
    let v'' = v' ++ reverse v'
    writeStd v''                     -- Write to stdout

Even though the examples are called bad and good, there's not a clear-cut answer to which version is best. It could depend on whether time or memory is the most scarce resource. This library leaves the decision in the hands of the programmer.

Working with matrices

2-dimensional matrix computations can follow a scheme similar to the above by using the types Manifest2, Pull2 and Push2 and the corresponding operations.

A quite common situation is the need to apply an operation on each row or column of a matrix. Operating on the rows can be done by a combination of exposeRows and hideRows. For example, this function reverses each row in a matrix:

revEachRow :: MonadComp m => Pull2 a -> Push2 m a
revEachRow mat = hideRows (numCols mat) $ map reverse $ exposeRows mat

exposeRows takes a Pully2 matrix and turns it into Pull (Pull a) i.e. a vector of row vectors. map is used to apply reverse to each row. Finally, hideRows turns the nested vector it back into a matrix, of type Push2.

Note that hideRows generally cannot know the length of the rows, so this number has to be provided as its first argument. When compiling with assertions, it will be checked at runtime that the length of each row is equal to the given length.

In order to operate on the columns instead of the rows, just apply transpose on the original matrix. This operation will fuse with the rest of the computation.

It gets a bit more complicated when the operation applied to each row is effectful. For example, the operation may have to use manifest internally giving it a monadic result type. In such situations, the function sequens is helpful. It is a bit similar to the standard function sequence for lists, execept that it converts Push m (m a) into Push m a; i.e. it embeds the effect into the resulting Push vector.

Here is a version of the previous example where the row operation is effectful (due to manifestFresh) and sequens is inserted to embed the effects:

revEachRowM :: (Syntax a, MonadComp m) => Pull2 a -> Push2 m a
revEachRowM mat = hideRows (numCols mat) $ sequens
                $ map (manifestFresh . reverse) $ exposeRows mat

Note that sequens is generally a dangerous function due to the hiding of effects inside the resulting vector. These effects may be (seemingly) randomly interleaved with other effects when the vector is used. However, the above example is fine, since manifestFresh allocates a fresh array for the storage, so its effects cannot be observed from the outside.

The comments to Push elaborate more on the semantics of push vectors with interleaved effects.

Synopsis

Documentation

class ViewManifest2 vec a => Manifestable2 m vec a | vec -> a where Source #

Minimal complete definition

Nothing

Methods

manifest2 Source #

Arguments

:: Syntax a 
=> Arr a

Where to store the result

-> vec

Vector to store

-> m (Manifest2 a) 

Write the contents of a vector to memory and get it back as a Manifest2 vector

manifest2 Source #

Arguments

:: (Pushy2 m vec a, Syntax a, MonadComp m) 
=> Arr a

Where to store the result

-> vec

Vector to store

-> m (Manifest2 a) 

Write the contents of a vector to memory and get it back as a Manifest2 vector

manifestFresh2 :: Syntax a => vec -> m (Manifest2 a) Source #

A version of manifest2 that allocates a fresh array for the result

manifestFresh2 :: (Finite2 vec, Syntax a, MonadComp m) => vec -> m (Manifest2 a) Source #

A version of manifest2 that allocates a fresh array for the result

manifestStore2 :: Syntax a => Arr a -> vec -> m () Source #

A version of manifest2 that only stores the vector to the given array (manifest2 is not guaranteed to use the array)

manifestStore2 :: (Pushy2 m vec a, Syntax a, MonadComp m) => Arr a -> vec -> m () Source #

A version of manifest2 that only stores the vector to the given array (manifest2 is not guaranteed to use the array)

Instances
MonadComp m => Manifestable2 m (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest2 :: Arr a -> Pull2 a -> m (Manifest2 a) Source #

manifestFresh2 :: Pull2 a -> m (Manifest2 a) Source #

manifestStore2 :: Arr a -> Pull2 a -> m () Source #

MonadComp m => Manifestable2 m (Manifest2 a) a Source #

manifest2 and manifestFresh2 are no-ops. manifestStore2 does a proper arrCopy.

Instance details

Defined in Feldspar.Data.Vector

(MonadComp m1, m1 ~ m2) => Manifestable2 m1 (Push2 m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest2 :: Arr a -> Push2 m2 a -> m1 (Manifest2 a) Source #

manifestFresh2 :: Push2 m2 a -> m1 (Manifest2 a) Source #

manifestStore2 :: Arr a -> Push2 m2 a -> m1 () Source #

class ViewManifest2 vec a | vec -> a where Source #

Minimal complete definition

Nothing

Methods

viewManifest2 :: vec -> Maybe (Manifest2 a) Source #

Try to cast a vector to Manifest2 directly

Instances
ViewManifest2 (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

ViewManifest2 (Manifest2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

ViewManifest2 (Push2 m a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest2 :: Push2 m a -> Maybe (Manifest2 a) Source #

class ViewManifest vec a => Manifestable m vec a | vec -> a where Source #

Minimal complete definition

Nothing

Methods

manifest Source #

Arguments

:: Syntax a 
=> Arr a

Where to store the vector

-> vec

Vector to store

-> m (Manifest a) 

Write the contents of a vector to memory and get it back as a Manifest vector. The supplied array may or may not be used for storage.

manifest Source #

Arguments

:: (Pushy m vec a, Finite vec, Syntax a, MonadComp m) 
=> Arr a

Where to store the vector

-> vec

Vector to store

-> m (Manifest a) 

Write the contents of a vector to memory and get it back as a Manifest vector. The supplied array may or may not be used for storage.

manifestFresh :: Syntax a => vec -> m (Manifest a) Source #

A version of manifest that allocates a fresh array for the result

manifestFresh :: (Finite vec, Syntax a, MonadComp m) => vec -> m (Manifest a) Source #

A version of manifest that allocates a fresh array for the result

manifestStore :: Syntax a => Arr a -> vec -> m () Source #

A version of manifest that only stores the vector to the given array (manifest is not guaranteed to use the array)

manifestStore :: (Pushy m vec a, Syntax a, MonadComp m) => Arr a -> vec -> m () Source #

A version of manifest that only stores the vector to the given array (manifest is not guaranteed to use the array)

Instances
MonadComp m => Manifestable m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Pull a -> m (Manifest a) Source #

manifestFresh :: Pull a -> m (Manifest a) Source #

manifestStore :: Arr a -> Pull a -> m () Source #

MonadComp m => Manifestable m (Manifest a) a Source #

manifest and manifestFresh are no-ops. manifestStore does a proper arrCopy.

Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Manifest a -> m (Manifest a) Source #

manifestFresh :: Manifest a -> m (Manifest a) Source #

manifestStore :: Arr a -> Manifest a -> m () Source #

(MonadComp m1, m1 ~ m2) => Manifestable m1 (Seq m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Seq m2 a -> m1 (Manifest a) Source #

manifestFresh :: Seq m2 a -> m1 (Manifest a) Source #

manifestStore :: Arr a -> Seq m2 a -> m1 () Source #

(MonadComp m1, m1 ~ m2) => Manifestable m1 (Push m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Push m2 a -> m1 (Manifest a) Source #

manifestFresh :: Push m2 a -> m1 (Manifest a) Source #

manifestStore :: Arr a -> Push m2 a -> m1 () Source #

class ViewManifest vec a | vec -> a where Source #

Minimal complete definition

Nothing

Methods

viewManifest :: vec -> Maybe (Manifest a) Source #

Try to cast a vector to Manifest directly

Instances
ViewManifest (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest :: Pull a -> Maybe (Manifest a) Source #

ViewManifest (Manifest a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

ViewManifest (Seq m a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest :: Seq m a -> Maybe (Manifest a) Source #

ViewManifest (Push m a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest :: Push m a -> Maybe (Manifest a) Source #

class Seqy m vec a | vec -> a where Source #

Vectors that can be converted to Seq

Methods

toSeq :: vec -> Seq m a Source #

Convert a vector to Seq

Instances
MonadComp m => Seqy m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toSeq :: Pull a -> Seq m a Source #

(Syntax a, MonadComp m) => Seqy m (Manifest a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toSeq :: Manifest a -> Seq m a Source #

m1 ~ m2 => Seqy m1 (Seq m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toSeq :: Seq m2 a -> Seq m1 a Source #

type DSeq m a = Seq m (Data a) Source #

Seq vector specialized to Data elements

data Seq m a where Source #

Finite sequential vector

Users interested in infinite streams are referred to the library: https://github.com/emilaxelsson/feldspar-synch

Constructors

Seq :: Data Length -> m (Data Index -> m a) -> Seq m a 
Instances
(MonadComp m1, m1 ~ m2) => Manifestable m1 (Seq m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Seq m2 a -> m1 (Manifest a) Source #

manifestFresh :: Seq m2 a -> m1 (Manifest a) Source #

manifestStore :: Arr a -> Seq m2 a -> m1 () Source #

m1 ~ m2 => Seqy m1 (Seq m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toSeq :: Seq m2 a -> Seq m1 a Source #

(MonadComp m1, m1 ~ m2) => Pushy m1 (Seq m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Seq m2 a -> Push m1 a Source #

Monad m => Functor (Seq m) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

fmap :: (a -> b) -> Seq m a -> Seq m b #

(<$) :: a -> Seq m b -> Seq m a #

Finite (Seq m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

length :: Seq m a -> Data Length Source #

(Syntax a, MarshalHaskell (Internal a), MarshalFeld a, m ~ Run) => MarshalFeld (Seq m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type HaskellRep (Seq m a) :: Type Source #

Methods

fwrite :: Handle -> Seq m a -> Run () Source #

fread :: Handle -> Run (Seq m a) Source #

ViewManifest (Seq m a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest :: Seq m a -> Maybe (Manifest a) Source #

type HaskellRep (Seq m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

class Pushy2 m vec a | vec -> a where Source #

Vectors that can be converted to Push2

Methods

toPush2 :: vec -> Push2 m a Source #

Convert a vector to Push2

Instances
MonadComp m => Pushy2 m (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Pull2 a -> Push2 m a Source #

MonadComp m => Pushy2 m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Pull a -> Push2 m a Source #

(Syntax a, MonadComp m) => Pushy2 m (Manifest2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Manifest2 a -> Push2 m a Source #

(Syntax a, MonadComp m) => Pushy2 m (Manifest a) a Source #

Convert to a Push2 with a single row

Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Manifest a -> Push2 m a Source #

m1 ~ m2 => Pushy2 m1 (Push2 m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Push2 m2 a -> Push2 m1 a Source #

type DPush2 m a = Push2 m (Data a) Source #

Push2 vector specialized to Data elements

data Push2 m a where Source #

2-dimensional push vector: a vector representation that supports nested write patterns (e.g. resulting from concatenation) and fusion of operations

See the comments to Push regarding the semantics of push vectors with interleaved effects.

Constructors

Push2 :: Data Length -> Data Length -> ((Data Index -> Data Index -> a -> m ()) -> m ()) -> Push2 m a 
Instances
(MonadComp m1, m1 ~ m2) => Manifestable2 m1 (Push2 m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest2 :: Arr a -> Push2 m2 a -> m1 (Manifest2 a) Source #

manifestFresh2 :: Push2 m2 a -> m1 (Manifest2 a) Source #

manifestStore2 :: Arr a -> Push2 m2 a -> m1 () Source #

m1 ~ m2 => Pushy2 m1 (Push2 m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Push2 m2 a -> Push2 m1 a Source #

Functor (Push2 m) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

fmap :: (a -> b) -> Push2 m a -> Push2 m b #

(<$) :: a -> Push2 m b -> Push2 m a #

Finite (Push2 m a) Source #

length gives number of rows

Instance details

Defined in Feldspar.Data.Vector

Methods

length :: Push2 m a -> Data Length Source #

(Syntax a, MarshalHaskell (Internal a), MarshalFeld a, m ~ Run) => MarshalFeld (Push2 m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type HaskellRep (Push2 m a) :: Type Source #

Methods

fwrite :: Handle -> Push2 m a -> Run () Source #

fread :: Handle -> Run (Push2 m a) Source #

Finite2 (Push2 m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

extent2 :: Push2 m a -> (Data Length, Data Length) Source #

ViewManifest2 (Push2 m a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest2 :: Push2 m a -> Maybe (Manifest2 a) Source #

type HaskellRep (Push2 m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

class Pushy m vec a | vec -> a where Source #

Vectors that can be converted to Push

Methods

toPush :: vec -> Push m a Source #

Convert a vector to Push

Instances
MonadComp m => Pushy m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Pull a -> Push m a Source #

(Syntax a, MonadComp m) => Pushy m (Manifest a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Manifest a -> Push m a Source #

(MonadComp m1, m1 ~ m2) => Pushy m1 (Seq m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Seq m2 a -> Push m1 a Source #

m1 ~ m2 => Pushy m1 (Push m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Push m2 a -> Push m1 a Source #

type DPush m a = Push m (Data a) Source #

Push vector specialized to Data elements

data Push m a where Source #

1-dimensional push vector: a vector representation that supports nested write patterns (e.g. resulting from concatenation) and fusion of operations

If it is the case that dumpPush v (\_ _ -> return ()) has the same behavior as return (), i.e., the vector does not have any embedded side effects, we can regard Push as a pure data structure with the denotation of a finite list.

However, Push is commonly used to assemble data after splitting it up and performing some operations on the parts. We want to be able to use Push even if the operation involved has side effects. The function sequens can be used to embed effects into a Push vector.

Push vectors with embedded effects can often be considered to be denoted by M [a], where M is some suitable monad. That is, the vector performs some effects and produces a finite list of values as a result. This denotation is enough to explain e.g. why

return (v ++ v)

is different from

do v' <- manifestFresh v
   return (v' ++ v')

(The former duplicates the embedded effects while the latter only performs the effects once.)

However, this denotation is not enough to model dumpPush, which allows a write method to be interleaved with the embedded effects. Even a function such as manifest can to some extent be used observe the order of effects (if the array argument to manifest is also updated by the internal effects).

Conclusion:

  • You can normally think of Push a as denoting M [a] (finite list)
  • Make sure to pass a free array as argument to manifest
  • Avoid using dumpPush unless you know that it's safe

Constructors

Push :: Data Length -> ((Data Index -> a -> m ()) -> m ()) -> Push m a 
Instances
(MonadComp m1, m1 ~ m2) => Manifestable m1 (Push m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Push m2 a -> m1 (Manifest a) Source #

manifestFresh :: Push m2 a -> m1 (Manifest a) Source #

manifestStore :: Arr a -> Push m2 a -> m1 () Source #

m1 ~ m2 => Pushy m1 (Push m2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Push m2 a -> Push m1 a Source #

Functor (Push m) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

fmap :: (a -> b) -> Push m a -> Push m b #

(<$) :: a -> Push m b -> Push m a #

Applicative (Push m) Source #

This instance behaves like the list instance:

pure x    = [x]
fs <*> xs = [f x | f <- fs, x <- xs]
Instance details

Defined in Feldspar.Data.Vector

Methods

pure :: a -> Push m a #

(<*>) :: Push m (a -> b) -> Push m a -> Push m b #

liftA2 :: (a -> b -> c) -> Push m a -> Push m b -> Push m c #

(*>) :: Push m a -> Push m b -> Push m b #

(<*) :: Push m a -> Push m b -> Push m a #

Finite (Push m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

length :: Push m a -> Data Length Source #

(Syntax a, MarshalHaskell (Internal a), MarshalFeld a, m ~ Run) => MarshalFeld (Push m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type HaskellRep (Push m a) :: Type Source #

Methods

fwrite :: Handle -> Push m a -> Run () Source #

fread :: Handle -> Run (Push m a) Source #

Finite2 (Push m a) Source #

Treated as a row vector

Instance details

Defined in Feldspar.Data.Vector

Methods

extent2 :: Push m a -> (Data Length, Data Length) 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 #

ViewManifest (Push m a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest :: Push m a -> Maybe (Manifest a) Source #

type HaskellRep (Push m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

type StoreRep (Push Comp a) Source # 
Instance details

Defined in Feldspar.Data.Storable

type StoreRep (Push Comp a) = (DRef Length, Arr a)
type StoreSize (Push Comp a) Source # 
Instance details

Defined in Feldspar.Data.Storable

class Pully2 vec a | vec -> a where Source #

Vectors that can be converted to Pull2

Methods

toPull2 :: vec -> Pull2 a Source #

Convert a vector to Pull2

Instances
(Indexed vec, Slicable vec, IndexedElem vec ~ a, Syntax a) => Pully2 (Nest vec) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPull2 :: Nest vec -> Pull2 a Source #

Pully2 (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPull2 :: Pull2 a -> Pull2 a Source #

Pully2 (Pull a) a Source #

Convert to a Pull2 with a single row

Instance details

Defined in Feldspar.Data.Vector

Methods

toPull2 :: Pull a -> Pull2 a Source #

Syntax a => Pully2 (Manifest a) a Source #

Convert to a Pull2 with a single row

Instance details

Defined in Feldspar.Data.Vector

Methods

toPull2 :: Manifest a -> Pull2 a Source #

type DPull2 a = Pull2 (Data a) Source #

Pull2 vector specialized to Data elements

data Pull2 a where Source #

2-dimensional pull vector: a vector representation that supports random access and fusion of operations

Constructors

Pull2 :: Data Length -> Data Length -> (Data Index -> Data Index -> a) -> Pull2 a 
Instances
Functor Pull2 Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

fmap :: (a -> b) -> Pull2 a -> Pull2 b #

(<$) :: a -> Pull2 b -> Pull2 a #

MonadComp m => Manifestable2 m (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest2 :: Arr a -> Pull2 a -> m (Manifest2 a) Source #

manifestFresh2 :: Pull2 a -> m (Manifest2 a) Source #

manifestStore2 :: Arr a -> Pull2 a -> m () Source #

MonadComp m => Pushy2 m (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Pull2 a -> Push2 m a Source #

Slicable (Pull2 a) Source #

Take a slice of the rows

Instance details

Defined in Feldspar.Data.Vector

Methods

slice :: Data Index -> Data Length -> Pull2 a -> Pull2 a Source #

Finite (Pull2 a) Source #

length gives number of rows

Instance details

Defined in Feldspar.Data.Vector

Methods

length :: Pull2 a -> Data Length Source #

Indexed (Pull2 a) Source #

Indexing the rows

Instance details

Defined in Feldspar.Data.Vector

Associated Types

type IndexedElem (Pull2 a) :: Type Source #

Methods

(!) :: Pull2 a -> Data Index -> IndexedElem (Pull2 a) Source #

(Syntax a, MarshalHaskell (Internal a), MarshalFeld a) => MarshalFeld (Pull2 a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type HaskellRep (Pull2 a) :: Type Source #

Methods

fwrite :: Handle -> Pull2 a -> Run () Source #

fread :: Handle -> Run (Pull2 a) Source #

Finite2 (Pull2 a) Source # 
Instance details

Defined in Feldspar.Data.Vector

ViewManifest2 (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Pully2 (Pull2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPull2 :: Pull2 a -> Pull2 a Source #

type IndexedElem (Pull2 a) Source # 
Instance details

Defined in Feldspar.Data.Vector

type IndexedElem (Pull2 a) = Pull a
type HaskellRep (Pull2 a) Source # 
Instance details

Defined in Feldspar.Data.Vector

class (Indexed vec, Finite vec, IndexedElem vec ~ a) => Pully vec a Source #

Data structures that are Pull-like (i.e. support ! and length)

Instances
(Indexed vec, Finite vec, IndexedElem vec ~ a) => Pully vec a Source # 
Instance details

Defined in Feldspar.Data.Vector

data VecChanSizeSpec lenSpec Source #

Constructors

VecChanSizeSpec (Data Length) lenSpec 

type DPull a = Pull (Data a) Source #

Pull vector specialized to Data elements

data Pull a where Source #

1-dimensional pull vector: a vector representation that supports random access and fusion of operations

Constructors

Pull :: Data Length -> (Data Index -> a) -> Pull a 
Instances
Functor Pull Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

fmap :: (a -> b) -> Pull a -> Pull b #

(<$) :: a -> Pull b -> Pull a #

MonadComp m => Manifestable m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

manifest :: Arr a -> Pull a -> m (Manifest a) Source #

manifestFresh :: Pull a -> m (Manifest a) Source #

manifestStore :: Arr a -> Pull a -> m () Source #

MonadComp m => Seqy m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toSeq :: Pull a -> Seq m a Source #

MonadComp m => Pushy2 m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush2 :: Pull a -> Push2 m a Source #

MonadComp m => Pushy m (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

toPush :: Pull a -> Push m a Source #

Slicable (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

slice :: Data Index -> Data Length -> Pull a -> Pull a Source #

Finite (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

length :: Pull a -> Data Length Source #

Indexed (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type IndexedElem (Pull a) :: Type Source #

Methods

(!) :: Pull a -> Data Index -> IndexedElem (Pull a) Source #

(Syntax a, MarshalHaskell (Internal a), MarshalFeld a) => MarshalFeld (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type HaskellRep (Pull a) :: Type Source #

Methods

fwrite :: Handle -> Pull a -> Run () Source #

fread :: Handle -> Run (Pull a) Source #

(Syntax a, BulkTransferable a, ContainerType a ~ Arr a) => Transferable (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Associated Types

type SizeSpec (Pull a) :: Type Source #

Finite2 (Pull a) Source #

Treated as a row vector

Instance details

Defined in Feldspar.Data.Vector

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 #

ViewManifest (Pull a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

viewManifest :: Pull a -> Maybe (Manifest a) Source #

Pully2 (Pull a) a Source #

Convert to a Pull2 with a single row

Instance details

Defined in Feldspar.Data.Vector

Methods

toPull2 :: Pull a -> Pull2 a Source #

type IndexedElem (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

type IndexedElem (Pull a) = a
type HaskellRep (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

type SizeSpec (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Vector

type StoreRep (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Storable

type StoreRep (Pull a) = (DRef Length, Arr a)
type StoreSize (Pull a) Source # 
Instance details

Defined in Feldspar.Data.Storable

type DManifest2 a = Manifest2 (Data a) Source #

Manifest2 vector specialized to Data elements

type Manifest2 a = Nest (Manifest a) Source #

A 2-dimensional vector with a concrete representation in memory

type DManifest a = DIArr a Source #

Manifest vector specialized to Data elements

type Manifest = IArr Source #

A 1-dimensional vector with a concrete representation in memory

There are two main reasons to use Manifest when possible instead of Pull:

  • The operations of the Manifestable class are more efficient for Manifest. They either result in a no-op or an efficient memory-copy (instead of a copying loop).
  • Manifest can be freely converted to/from a 2-dimensional structure using nest and unnest. Note that the representation of Manifest2 is Nest (Manifest a).

listManifest :: (Syntax a, MonadComp m) => [a] -> m (Manifest a) Source #

Make a Manifest vector from a list of values

ofLength :: Data Length -> lenSpec -> VecChanSizeSpec lenSpec Source #

toPull :: Pully vec a => vec -> Pull a Source #

Convert a vector to Pull

head :: Pully vec a => vec -> a Source #

Take the head of a non-empty vector

tail :: Pully vec a => vec -> Pull a Source #

take :: Pully vec a => Data Length -> vec -> Pull a Source #

drop :: Pully vec a => Data Length -> vec -> Pull a Source #

tails :: Pully vec a => vec -> Pull (Pull a) Source #

inits :: Pully vec a => vec -> Pull (Pull a) Source #

inits1 :: Pully vec a => vec -> Pull (Pull a) Source #

map :: Pully vec a => (a -> b) -> vec -> Pull b Source #

zip :: (Pully vec1 a, Pully vec2 b) => vec1 -> vec2 -> Pull (a, b) Source #

backPermute :: Pully vec a => (Data Length -> Data Index -> Data Index) -> vec -> Pull a Source #

Back-permute a Pull vector using an index mapping. The supplied mapping must be a bijection when restricted to the domain of the vector. This property is not checked, so use with care.

reverse :: Pully vec a => vec -> Pull a Source #

zipWith :: (Pully vec1 a, Pully vec2 b) => (a -> b -> c) -> vec1 -> vec2 -> Pull c Source #

fold :: (Syntax a, Pully vec a) => (a -> a -> a) -> a -> vec -> a Source #

Left fold of a vector

fold1 :: (Syntax a, Pully vec a) => (a -> a -> a) -> vec -> a Source #

Left fold of a non-empty vector

sum :: (Pully vec a, Syntax a, Num a) => vec -> a Source #

scProd :: (Num a, Syntax a, Pully vec1 a, Pully vec2 a) => vec1 -> vec2 -> a Source #

Scalar product

toPull2' :: Pully2 vec a => vec -> Pull2 a Source #

Transposed version of toPull. Can be used to e.g. turn a Pull into a column of a matrix

hideRowsPull Source #

Arguments

:: (Pully vec1 vec2, Pully vec2 a) 
=> Data Length

Length of inner vectors

-> vec1 
-> Pull2 a 

Turn a vector of rows into a 2-dimensional vector. All inner vectors are assumed to have the given length, and this assumption is not checked by assertions. If types permit, it is preferable to use hideRows, which does check the lengths.

exposeRows :: Pully2 vec a => vec -> Pull (Pull a) Source #

Expose the rows in a Pull2 by turning it into a vector of rows

transpose :: Pully2 vec a => vec -> Pull2 a Source #

Transpose of a matrix

toRowVec :: Pully vec a => vec -> Pull2 a Source #

fromRowVec :: Pully2 vec a => vec -> Pull a Source #

toColVec :: Pully vec a => vec -> Pull2 a Source #

fromColVec :: Pully2 vec a => vec -> Pull a Source #

matMul :: (Pully2 vec1 a, Pully2 vec2 a, Num a, Syntax a) => vec1 -> vec2 -> Pull2 a Source #

Matrix multiplication

toPushM :: (Pushy m vec a, Monad m) => vec -> m (Push m a) Source #

A version of toPush that constrains the m argument of Push to that of the monad in which the result is returned. This can be a convenient way to avoid unresolved overloading.

dumpPush Source #

Arguments

:: Push m a

Vector to dump

-> (Data Index -> a -> m ())

Function that writes one element

-> m () 

Dump the contents of a Push vector

listPush :: Monad m => [a] -> Push m a Source #

Create a Push vector from a list of elements

(++) :: (Pushy m vec1 a, Pushy m vec2 a, Monad m) => vec1 -> vec2 -> Push m a Source #

Append two vectors to make a Push vector

concat Source #

Arguments

:: (Pushy m vec1 vec2, Pushy m vec2 a, MonadComp m) 
=> Data Length

Length of inner vectors

-> vec1 
-> Push m a 

flatten :: Pushy2 m vec a => vec -> Push m a Source #

sequens :: (Pushy m vec (m a), Monad m) => vec -> Push m a Source #

Embed the effects in the elements into the internal effects of a Push vector

WARNING: This function should be used with care, since it allows hiding effects inside a vector. These effects may be (seemingly) randomly interleaved with other effects when the vector is used.

The name sequens has to do with the similarity to the standard function sequence.

forwardPermute :: Pushy m vec a => (Data Length -> Data Index -> Data Index) -> vec -> Push m a Source #

Forward-permute a Push vector using an index mapping. The supplied mapping must be a bijection when restricted to the domain of the vector. This property is not checked, so use with care.

unroll Source #

Arguments

:: (Pully vec a, MonadComp m) 
=> Length

Number of steps to unroll

-> vec 
-> Push m a 

Convert a vector to a push vector that computes n elements in each step. This can be used to achieve loop unrolling.

The length of the vector must be divisible by the number of unrolling steps.

toPushM2 :: (Pushy2 m vec a, Monad m) => vec -> m (Push2 m a) Source #

A version of toPush2 that constrains the m argument of Push2 to that of the monad in which the result is returned. This can be a convenient way to avoid unresolved overloading.

dumpPush2 Source #

Arguments

:: Push2 m a

Vector to dump

-> (Data Index -> Data Index -> a -> m ())

Function that writes one element

-> m () 

Dump the contents of a Push2 vector

hideRows Source #

Arguments

:: (Pushy m vec1 vec2, Pushy m vec2 a, MonadComp m) 
=> Data Length

Length of inner vectors

-> vec1 
-> Push2 m a 

Turn a vector of rows into a 2-dimensional vector. All inner vectors are assumed to have the given length.

sequens2 :: (Pushy2 m vec (m a), Monad m) => vec -> Push2 m a Source #

Convert a 2-dimensional vector with effectful elements to Push2

WARNING: This function should be used with care, since is allows hiding effects inside a vector. These effects may be (seemingly) randomly interleaved with other effects when the vector is used.

The name sequens2 has to do with the similarity to the standard function sequence.

forwardPermute2 :: Pushy2 m vec a => (Data Length -> Data Length -> (Data Index, Data Index) -> (Data Index, Data Index)) -> vec -> Push2 m a Source #

Forward-permute a Push vector using an index mapping. The supplied mapping must be a bijection when restricted to the domain of the vector. This property is not checked, so use with care.

transposePush :: Pushy2 m vec a => vec -> Push2 m a Source #

toSeqM :: (Seqy m vec a, Monad m) => vec -> m (Seq m a) Source #

A version of toSeq that constrains the m argument of Seq to that of the monad in which the result is returned. This can be a convenient way to avoid unresolved overloading.

zipWithSeq :: (Seqy m vec1 a, Seqy m vec2 b, Monad m) => (a -> b -> c) -> vec1 -> vec2 -> Seq m c Source #

unfold :: (Syntax b, MonadComp m) => Data Length -> (b -> (b, a)) -> b -> Seq m a Source #

mapAccum' :: (Seqy m vec a, Syntax acc, MonadComp m) => (acc -> a -> (acc, b)) -> acc -> vec -> Seq m (acc, b) Source #

mapAccum :: (Seqy m vec a, Syntax acc, MonadComp m) => (acc -> a -> (acc, b)) -> acc -> vec -> Seq m b Source #

scan :: (Seqy m vec b, Syntax a, MonadComp m) => (a -> b -> a) -> a -> vec -> Seq m a Source #

This function behaves slightly differently from the standard scanl for lists:

  • The initial element is not included in the output
  • Thus, the output has the same length as the input

Orphan instances

(Syntax a, BulkTransferable a, ContainerType a ~ Arr a) => Transferable (IArr a) Source # 
Instance details

Associated Types

type SizeSpec (IArr a) :: Type Source #

(Syntax a, BulkTransferable a, ContainerType a ~ Arr a) => Transferable (Arr a) Source # 
Instance details

Associated Types

type SizeSpec (Arr a) :: Type Source #

Finite2 (Manifest a) Source #

Treated as a row vector

Instance details