raw-feldspar-0.3: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Data.Array

Contents

Description

Data structures for working with arrays

Synopsis

Documentation

data Nest a Source #

Nested data structure (see explanation of nest)

Instances
Functor Nest Source # 
Instance details

Defined in Feldspar.Data.Array

Methods

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

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

Foldable Nest Source # 
Instance details

Defined in Feldspar.Data.Array

Methods

fold :: Monoid m => Nest m -> m #

foldMap :: Monoid m => (a -> m) -> Nest a -> m #

foldr :: (a -> b -> b) -> b -> Nest a -> b #

foldr' :: (a -> b -> b) -> b -> Nest a -> b #

foldl :: (b -> a -> b) -> b -> Nest a -> b #

foldl' :: (b -> a -> b) -> b -> Nest a -> b #

foldr1 :: (a -> a -> a) -> Nest a -> a #

foldl1 :: (a -> a -> a) -> Nest a -> a #

toList :: Nest a -> [a] #

null :: Nest a -> Bool #

length :: Nest a -> Int #

elem :: Eq a => a -> Nest a -> Bool #

maximum :: Ord a => Nest a -> a #

minimum :: Ord a => Nest a -> a #

sum :: Num a => Nest a -> a #

product :: Num a => Nest a -> a #

Traversable Nest Source # 
Instance details

Defined in Feldspar.Data.Array

Methods

traverse :: Applicative f => (a -> f b) -> Nest a -> f (Nest b) #

sequenceA :: Applicative f => Nest (f a) -> f (Nest a) #

mapM :: Monad m => (a -> m b) -> Nest a -> m (Nest b) #

sequence :: Monad m => Nest (m a) -> m (Nest a) #

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

(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 #

Slicable a => Slicable (Nest a) Source # 
Instance details

Defined in Feldspar.Data.Array

Methods

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

Finite (Nest a) Source # 
Instance details

Defined in Feldspar.Data.Array

Methods

length :: Nest a -> Data Length Source #

Slicable a => Indexed (Nest a) Source # 
Instance details

Defined in Feldspar.Data.Array

Associated Types

type IndexedElem (Nest a) :: Type Source #

Methods

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

MarshalFeld a => MarshalFeld (Nest a) Source #

Note that HaskellRep (Nest a) = (Length, Length, HaskellRep a) rather than [HaskellRep a]. This means that e.g. Nest (Nest (Fin (IArr a))) is represented as (Length,Length,(Length,Length,(Length,[...]))) instead of the more convenient [[...]].

Instance details

Defined in Feldspar.Data.Array

Associated Types

type HaskellRep (Nest a) :: Type Source #

Methods

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

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

Finite2 (Nest a) Source # 
Instance details

Defined in Feldspar.Data.Array

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 #

ViewManifest2 (Manifest2 a) a Source # 
Instance details

Defined in Feldspar.Data.Vector

(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 #

type IndexedElem (Nest a) Source # 
Instance details

Defined in Feldspar.Data.Array

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

Defined in Feldspar.Data.Array

type StoreRep (Manifest2 a) Source # 
Instance details

Defined in Feldspar.Data.Storable

type StoreSize (Manifest2 a) Source # 
Instance details

Defined in Feldspar.Data.Storable

nest Source #

Arguments

:: Finite a 
=> Data Length

Number of segments

-> Data Length

Segment length

-> a 
-> Nest a 

Add a layer of nesting to a linear data structure by virtually chopping it up into segments. The nesting is virtual in the sense that unnest (nest h w a) is syntactically identical to a.

In an expression nest l w a, it must be the case that l*w == length a.

multiNest may be a more convenient alternative to nest, expecially for adding several levels of nesting.

nestEvery Source #

Arguments

:: Finite a 
=> Data Length

Segment length

-> a 
-> Nest a 

A version of nest that only takes the segment length as argument. The total number of segments is computed by division.

In an expression nestEvery n a, it must be the case that div (length a) n * n == length a.

This assumption permits removing the division in many cases when the nested structure is later flattened in some way.

unnest :: Slicable a => Nest a -> a Source #

Remove a layer of nesting

data Dim d Source #

Increase dimensionality

This type is used to represent the number of dimensions of a multi-dimensional structure. For example, Dim (Dim ()) means two dimensions (see the aliases Dim1, Dim2, etc.).

type Dim1 = Dim () Source #

One dimension

type Dim2 = Dim Dim1 Source #

Two dimensions

type Dim3 = Dim Dim2 Source #

Three dimensions

type Dim4 = Dim Dim3 Source #

Four dimensions

data InnerExtent d where Source #

A description of the inner extent of a rectangular multi-dimensional structure. "Inner extent" means the extent of all but the outermost dimension.

For example, this value

Outer :> 10 :> 20 :: InnerExtent (Dim (Dim (Dim ())))

describes a three-dimensional structure where each inner structure has 10 rows and 20 columns.

Constructors

NoExt :: InnerExtent () 
Outer :: InnerExtent (Dim ()) 
(:>) :: InnerExtent (Dim d) -> Data Length -> InnerExtent (Dim (Dim d)) infixl 5 

listExtent :: InnerExtent d -> [Data Length] Source #

Return the inner extent as a list of lengths

type family MultiNest d a where ... Source #

Add as much nesting to a one-dimensional structure as needed to reach the given dimensionality

Equations

MultiNest (Dim ()) a = a 
MultiNest (Dim (Dim d)) a = Nest (MultiNest (Dim d) a) 

multiNest :: forall a d. Finite a => InnerExtent (Dim d) -> a -> MultiNest (Dim d) a Source #

Turn a one-dimensional structure into a multi-dimensional one by adding nesting as described by the given InnerExtent

data InnerExtent' d where Source #

A version of InnerExtent for internal use

Constructors

ZE :: InnerExtent' () 
OE :: InnerExtent' (Dim ()) 
SE :: Data Length -> InnerExtent' d -> InnerExtent' (Dim d) 

2-dimensional arrays

class Finite2 a where Source #

Methods

extent2 Source #

Arguments

:: a 
-> (Data Length, Data Length)
(rows,columns)

Get the extent of a 2-dimensional vector

It must hold that:

numRows == length
Instances
Finite2 (Nest a) Source # 
Instance details

Defined in Feldspar.Data.Array

Finite2 (Pull2 a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Finite2 (Pull a) Source #

Treated as a row vector

Instance details

Defined in Feldspar.Data.Vector

Finite2 (Manifest a) Source #

Treated as a row vector

Instance details

Defined in Feldspar.Data.Vector

Finite2 (Push2 m a) Source # 
Instance details

Defined in Feldspar.Data.Vector

Methods

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

numRows :: Finite2 a => a -> Data Length Source #

Get the number of rows of a two-dimensional structure

numRows == length

numCols :: Finite2 a => a -> Data Length Source #

Get the number of columns of a two-dimensional structure