Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module gives a library of different vector types.
Basic use
A typical 1-dimensional vector computation goes as follows:
- Start with a
Manifest
vector (one that is refers directly to an array in memory). - Apply operations overloaded by
Pully
(e.g.take
,drop
,map
,reverse
). The result is one or morePull
vectors. - If the previous step resulted in several parts, assemble them using
operations overloaded by
Pushy
(e.g.++
). The result is aPush
vector. - Write the vector to memory using
manifest
ormanifestFresh
.
(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
i.e. a vector of row vectors. Pull
(Pull
a)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
into Push
m (m a)
; i.e. it
embeds the effect into the resulting Push
m aPush
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.
- module Feldspar.Data.Array
- type Manifest = IArr
- type DManifest a = DIArr a
- listManifest :: (Syntax a, MonadComp m) => [a] -> m (Manifest a)
- type Manifest2 a = Nest (Manifest a)
- type DManifest2 a = Manifest2 (Data a)
- data Pull a where
- type DPull a = Pull (Data a)
- data VecChanSizeSpec lenSpec = VecChanSizeSpec (Data Length) lenSpec
- ofLength :: Data Length -> lenSpec -> VecChanSizeSpec lenSpec
- class (Indexed vec, Finite vec, IndexedElem vec ~ a) => Pully vec a
- toPull :: Pully vec a => vec -> Pull a
- head :: Pully vec a => vec -> a
- tail :: Pully vec a => vec -> Pull a
- take :: Pully vec a => Data Length -> vec -> Pull a
- drop :: Pully vec a => Data Length -> vec -> Pull a
- tails :: Pully vec a => vec -> Pull (Pull a)
- inits :: Pully vec a => vec -> Pull (Pull a)
- inits1 :: Pully vec a => vec -> Pull (Pull a)
- replicate :: Data Length -> a -> Pull a
- map :: Pully vec a => (a -> b) -> vec -> Pull b
- zip :: (Pully vec1 a, Pully vec2 b) => vec1 -> vec2 -> Pull (a, b)
- backPermute :: Pully vec a => (Data Length -> Data Index -> Data Index) -> vec -> Pull a
- reverse :: Pully vec a => vec -> Pull a
- (...) :: Data Index -> Data Index -> Pull (Data Index)
- zipWith :: (Pully vec1 a, Pully vec2 b) => (a -> b -> c) -> vec1 -> vec2 -> Pull c
- fold :: (Syntax a, Pully vec a) => (a -> a -> a) -> a -> vec -> a
- fold1 :: (Syntax a, Pully vec a) => (a -> a -> a) -> vec -> a
- sum :: (Pully vec a, Syntax a, Num a) => vec -> a
- scProd :: (Num a, Syntax a, Pully vec1 a, Pully vec2 a) => vec1 -> vec2 -> a
- data Pull2 a where
- type DPull2 a = Pull2 (Data a)
- class Pully2 vec a | vec -> a where
- toPull2' :: Pully2 vec a => vec -> Pull2 a
- hideRowsPull :: (Pully vec1 vec2, Pully vec2 a) => Data Length -> vec1 -> Pull2 a
- exposeRows :: Pully2 vec a => vec -> Pull (Pull a)
- transpose :: Pully2 vec a => vec -> Pull2 a
- toRowVec :: Pully vec a => vec -> Pull2 a
- fromRowVec :: Pully2 vec a => vec -> Pull a
- toColVec :: Pully vec a => vec -> Pull2 a
- fromColVec :: Pully2 vec a => vec -> Pull a
- matMul :: (Pully2 vec1 a, Pully2 vec2 a, Num a, Syntax a) => vec1 -> vec2 -> Pull2 a
- data Push m a where
- type DPush m a = Push m (Data a)
- class Pushy m vec a | vec -> a where
- toPushM :: (Pushy m vec a, Monad m) => vec -> m (Push m a)
- dumpPush :: Push m a -> (Data Index -> a -> m ()) -> m ()
- listPush :: Monad m => [a] -> Push m a
- (++) :: (Pushy m vec1 a, Pushy m vec2 a, Monad m) => vec1 -> vec2 -> Push m a
- concat :: (Pushy m vec1 vec2, Pushy m vec2 a, MonadComp m) => Data Length -> vec1 -> Push m a
- flatten :: Pushy2 m vec a => vec -> Push m a
- sequens :: (Pushy m vec (m a), Monad m) => vec -> Push m a
- forwardPermute :: Pushy m vec a => (Data Length -> Data Index -> Data Index) -> vec -> Push m a
- unroll :: (Pully vec a, MonadComp m) => Length -> vec -> Push m a
- data Push2 m a where
- type DPush2 m a = Push2 m (Data a)
- class Pushy2 m vec a | vec -> a where
- toPushM2 :: (Pushy2 m vec a, Monad m) => vec -> m (Push2 m a)
- dumpPush2 :: Push2 m a -> (Data Index -> Data Index -> a -> m ()) -> m ()
- hideRows :: (Pushy m vec1 vec2, Pushy m vec2 a, MonadComp m) => Data Length -> vec1 -> Push2 m a
- sequens2 :: (Pushy2 m vec (m a), Monad m) => vec -> Push2 m a
- forwardPermute2 :: Pushy2 m vec a => (Data Length -> Data Length -> (Data Index, Data Index) -> (Data Index, Data Index)) -> vec -> Push2 m a
- transposePush :: Pushy2 m vec a => vec -> Push2 m a
- data Seq m a where
- type DSeq m a = Seq m (Data a)
- class Seqy m vec a | vec -> a where
- toSeqM :: (Seqy m vec a, Monad m) => vec -> m (Seq m a)
- zipWithSeq :: (Seqy m vec1 a, Seqy m vec2 b, Monad m) => (a -> b -> c) -> vec1 -> vec2 -> Seq m c
- unfold :: (Syntax b, MonadComp m) => Data Length -> (b -> (b, a)) -> b -> Seq m a
- mapAccum' :: (Seqy m vec a, Syntax acc, MonadComp m) => (acc -> a -> (acc, b)) -> acc -> vec -> Seq m (acc, b)
- mapAccum :: (Seqy m vec a, Syntax acc, MonadComp m) => (acc -> a -> (acc, b)) -> acc -> vec -> Seq m b
- scan :: (Seqy m vec b, Syntax a, MonadComp m) => (a -> b -> a) -> a -> vec -> Seq m a
- class ViewManifest vec a | vec -> a where
- class ViewManifest vec a => Manifestable m vec a | vec -> a where
- class ViewManifest2 vec a | vec -> a where
- class ViewManifest2 vec a => Manifestable2 m vec a | vec -> a where
Documentation
module Feldspar.Data.Array
1-dimensional manifest vectors
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 forManifest
. 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 usingnest
andunnest
. Note that the representation ofManifest2
is
.Nest
(Manifest
a)
listManifest :: (Syntax a, MonadComp m) => [a] -> m (Manifest a) Source #
Make a Manifest
vector from a list of values
2-dimensional manifest vectors
type Manifest2 a = Nest (Manifest a) Source #
A 2-dimensional vector with a concrete representation in memory
1-dimensional pull vectors
1-dimensional pull vector: a vector representation that supports random access and fusion of operations
Functor Pull Source # | |
MonadComp m => Manifestable m (Pull a) a Source # | |
MonadComp m => Seqy m (Pull a) a Source # | |
MonadComp m => Pushy2 m (Pull a) a Source # | |
MonadComp m => Pushy m (Pull a) a Source # | |
Slicable (Pull a) Source # | |
Finite (Pull a) Source # | |
Indexed (Pull a) Source # | |
(Syntax a, BulkTransferable a, (~) * (ContainerType a) (Arr a)) => Transferable (Pull a) Source # | |
(Syntax a, MarshalHaskell (Internal a), MarshalFeld a) => MarshalFeld (Pull a) Source # | |
Finite2 (Pull a) Source # | Treated as a row vector |
Syntax a => Storable (Pull a) Source # | |
ViewManifest (Pull a) a Source # | |
Pully2 (Pull a) a Source # | Convert to a |
type IndexedElem (Pull a) Source # | |
type SizeSpec (Pull a) Source # | |
type HaskellRep (Pull a) Source # | |
type StoreRep (Pull a) Source # | |
type StoreSize (Pull a) Source # | |
data VecChanSizeSpec lenSpec Source #
VecChanSizeSpec (Data Length) lenSpec |
Operations
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.
fold1 :: (Syntax a, Pully vec a) => (a -> a -> a) -> vec -> a Source #
Left fold of a non-empty vector
2-dimensional pull vectors
2-dimensional pull vector: a vector representation that supports random access and fusion of operations
Functor Pull2 Source # | |
MonadComp m => Manifestable2 m (Pull2 a) a Source # | |
MonadComp m => Pushy2 m (Pull2 a) a Source # | |
Slicable (Pull2 a) Source # | Take a slice of the rows |
Finite (Pull2 a) Source # |
|
Indexed (Pull2 a) Source # | Indexing the rows |
(Syntax a, MarshalHaskell (Internal a), MarshalFeld a) => MarshalFeld (Pull2 a) Source # | |
Finite2 (Pull2 a) Source # | |
ViewManifest2 (Pull2 a) a Source # | |
Pully2 (Pull2 a) a Source # | |
type IndexedElem (Pull2 a) Source # | |
type HaskellRep (Pull2 a) Source # | |
Operations
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
fromRowVec :: Pully2 vec a => vec -> Pull 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
1-dimensional push vectors
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
has the same
behavior as dumpPush
v (\_ _ -> return
())
, i.e., the vector does not have any embedded side
effects, we can regard return
()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
vreturn
(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:
(MonadComp m1, (~) (* -> *) m1 m2) => Manifestable m1 (Push m2 a) a Source # | |
(~) (* -> *) m1 m2 => Pushy m1 (Push m2 a) a Source # | |
Functor (Push m) Source # | |
Applicative (Push m) Source # | This instance behaves like the list instance: pure x = [x] fs <*> xs = [f x | f <- fs, x <- xs] |
Finite (Push m a) Source # | |
(Syntax a, MarshalHaskell (Internal a), MarshalFeld a, (~) (* -> *) m Run) => MarshalFeld (Push m a) Source # | |
Finite2 (Push m a) Source # | Treated as a row vector |
Syntax a => Storable (Push Comp a) Source # | |
ViewManifest (Push m a) a Source # | |
type HaskellRep (Push m a) Source # | |
type StoreRep (Push Comp a) Source # | |
type StoreSize (Push Comp a) Source # | |
Dump the contents of a Push
vector
Operations
(++) :: (Pushy m vec1 a, Pushy m vec2 a, Monad m) => vec1 -> vec2 -> Push m a Source #
Append two vectors to make a Push
vector
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.
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.
2-dimensional push vectors
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.
Push2 :: Data Length -> Data Length -> ((Data Index -> Data Index -> a -> m ()) -> m ()) -> Push2 m a |
(MonadComp m1, (~) (* -> *) m1 m2) => Manifestable2 m1 (Push2 m2 a) a Source # | |
(~) (* -> *) m1 m2 => Pushy2 m1 (Push2 m2 a) a Source # | |
Functor (Push2 m) Source # | |
Finite (Push2 m a) Source # |
|
(Syntax a, MarshalHaskell (Internal a), MarshalFeld a, (~) (* -> *) m Run) => MarshalFeld (Push2 m a) Source # | |
Finite2 (Push2 m a) Source # | |
ViewManifest2 (Push2 m a) a Source # | |
type HaskellRep (Push2 m a) Source # | |
class Pushy2 m vec a | vec -> a where Source #
Vectors that can be converted to Push2
MonadComp m => Pushy2 m (Pull2 a) a Source # | |
MonadComp m => Pushy2 m (Pull a) a Source # | |
(Syntax a, MonadComp m) => Pushy2 m (Manifest2 a) a Source # | |
(Syntax a, MonadComp m) => Pushy2 m (Manifest a) a Source # | Convert to a |
(~) (* -> *) m1 m2 => Pushy2 m1 (Push2 m2 a) a Source # | |
:: 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
Operations
:: (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 #
Sequential vectors
Finite sequential vector
Users interested in infinite streams are referred to the library: https://github.com/emilaxelsson/feldspar-synch
(MonadComp m1, (~) (* -> *) m1 m2) => Manifestable m1 (Seq m2 a) a Source # | |
(~) (* -> *) m1 m2 => Seqy m1 (Seq m2 a) a Source # | |
(MonadComp m1, (~) (* -> *) m1 m2) => Pushy m1 (Seq m2 a) a Source # | |
Monad m => Functor (Seq m) Source # | |
Finite (Seq m a) Source # | |
(Syntax a, MarshalHaskell (Internal a), MarshalFeld a, (~) (* -> *) m Run) => MarshalFeld (Seq m a) Source # | |
ViewManifest (Seq m a) a Source # | |
type HaskellRep (Seq m a) Source # | |
zipWithSeq :: (Seqy m vec1 a, Seqy m vec2 b, Monad m) => (a -> b -> c) -> vec1 -> vec2 -> Seq m c 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
Writing to memory
class ViewManifest vec a | vec -> a where Source #
ViewManifest (Pull a) a Source # | |
ViewManifest (Manifest a) a Source # | |
ViewManifest (Seq m a) a Source # | |
ViewManifest (Push m a) a Source # | |
class ViewManifest vec a => Manifestable m vec a | vec -> a where Source #
manifest :: Syntax a => Arr a -> vec -> m (Manifest a) Source #
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 :: (Pushy m vec a, Finite vec, Syntax a, MonadComp m) => Arr a -> vec -> m (Manifest a) Source #
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 #
MonadComp m => Manifestable m (Pull a) a Source # | |
MonadComp m => Manifestable m (Manifest a) a Source # |
|
(MonadComp m1, (~) (* -> *) m1 m2) => Manifestable m1 (Seq m2 a) a Source # | |
(MonadComp m1, (~) (* -> *) m1 m2) => Manifestable m1 (Push m2 a) a Source # | |
class ViewManifest2 vec a | vec -> a where Source #
ViewManifest2 (Pull2 a) a Source # | |
ViewManifest2 (Manifest2 a) a Source # | |
ViewManifest2 (Push2 m a) a Source # | |
class ViewManifest2 vec a => Manifestable2 m vec a | vec -> a where Source #
manifest2 :: Syntax a => Arr a -> vec -> m (Manifest2 a) Source #
Write the contents of a vector to memory and get it back as a
Manifest2
vector
manifest2 :: (Pushy2 m vec a, Syntax a, MonadComp m) => Arr a -> vec -> m (Manifest2 a) Source #
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 #
MonadComp m => Manifestable2 m (Pull2 a) a Source # | |
MonadComp m => Manifestable2 m (Manifest2 a) a Source # |
|
(MonadComp m1, (~) (* -> *) m1 m2) => Manifestable2 m1 (Push2 m2 a) a Source # | |
Orphan instances
(Syntax a, BulkTransferable a, (~) * (ContainerType a) (Arr a)) => Transferable (IArr a) Source # | |
(Syntax a, BulkTransferable a, (~) * (ContainerType a) (Arr a)) => Transferable (Arr a) Source # | |
Finite2 (Manifest a) Source # | Treated as a row vector |