Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Definition of Second-Order Array Combinators (SOACs), which are the main form of parallelism in the early stages of the compiler.
Synopsis
- data SOAC lore
- data StreamOrd
- data StreamForm lore
- = Parallel StreamOrd Commutativity (Lambda lore)
- | Sequential
- data ScremaForm lore = ScremaForm [Scan lore] [Reduce lore] (Lambda lore)
- data HistOp lore = HistOp {
- histWidth :: SubExp
- histRaceFactor :: SubExp
- histDest :: [VName]
- histNeutral :: [SubExp]
- histOp :: Lambda lore
- data Scan lore = Scan {
- scanLambda :: Lambda lore
- scanNeutral :: [SubExp]
- scanResults :: [Scan lore] -> Int
- singleScan :: Bindable lore => [Scan lore] -> Scan lore
- data Reduce lore = Reduce {
- redComm :: Commutativity
- redLambda :: Lambda lore
- redNeutral :: [SubExp]
- redResults :: [Reduce lore] -> Int
- singleReduce :: Bindable lore => [Reduce lore] -> Reduce lore
- scremaType :: SubExp -> ScremaForm lore -> [Type]
- soacType :: SOAC lore -> [Type]
- typeCheckSOAC :: Checkable lore => SOAC (Aliases lore) -> TypeM lore ()
- mkIdentityLambda :: (Bindable lore, MonadFreshNames m) => [Type] -> m (Lambda lore)
- isIdentityLambda :: Lambda lore -> Bool
- nilFn :: Bindable lore => Lambda lore
- scanomapSOAC :: [Scan lore] -> Lambda lore -> ScremaForm lore
- redomapSOAC :: [Reduce lore] -> Lambda lore -> ScremaForm lore
- scanSOAC :: (Bindable lore, MonadFreshNames m) => [Scan lore] -> m (ScremaForm lore)
- reduceSOAC :: (Bindable lore, MonadFreshNames m) => [Reduce lore] -> m (ScremaForm lore)
- mapSOAC :: Lambda lore -> ScremaForm lore
- isScanomapSOAC :: ScremaForm lore -> Maybe ([Scan lore], Lambda lore)
- isRedomapSOAC :: ScremaForm lore -> Maybe ([Reduce lore], Lambda lore)
- isScanSOAC :: ScremaForm lore -> Maybe [Scan lore]
- isReduceSOAC :: ScremaForm lore -> Maybe [Reduce lore]
- isMapSOAC :: ScremaForm lore -> Maybe (Lambda lore)
- ppScrema :: (PrettyLore lore, Pretty inp) => SubExp -> [inp] -> ScremaForm lore -> Doc
- ppHist :: (PrettyLore lore, Pretty inp) => SubExp -> [HistOp lore] -> Lambda lore -> [inp] -> Doc
- groupScatterResults :: [(Shape, Int, array)] -> [a] -> [(Shape, array, [([a], a)])]
- groupScatterResults' :: [(Shape, Int, array)] -> [a] -> [([a], a)]
- splitScatterResults :: [(Shape, Int, array)] -> [a] -> ([a], [a])
- data SOACMapper flore tlore m = SOACMapper {
- mapOnSOACSubExp :: SubExp -> m SubExp
- mapOnSOACLambda :: Lambda flore -> m (Lambda tlore)
- mapOnSOACVName :: VName -> m VName
- identitySOACMapper :: Monad m => SOACMapper lore lore m
- mapSOACM :: (Applicative m, Monad m) => SOACMapper flore tlore m -> SOAC flore -> m (SOAC tlore)
Documentation
A second-order array combinator (SOAC).
Stream SubExp [VName] (StreamForm lore) [SubExp] (Lambda lore) | |
Scatter SubExp (Lambda lore) [VName] [(Shape, Int, VName)] | Scatter length lambda inputs outputs Scatter maps values from a set of input arrays to indices and values of a set of output arrays. It is able to write multiple values to multiple outputs each of which may have multiple dimensions. inputs is a list of input arrays, all having size length, elements of which are applied to the lambda function. For instance, if there are two arrays, lambda will get two values as input, one from each array. outputs specifies the result of the lambda and which arrays to write to. Each element of the list consists of a VName specifying which array to scatter to, a Shape describing the shape of that array, and an Int describing how many elements should be written to that array for each invocation of the lambda. lambda is a function that takes inputs from inputs and returns values according to the output-specification in outputs. It returns values in the following manner:
For each output in outputs, lambda returns i * j index values and j output values, where i is the number of dimensions (rank) of the given output, and j is the number of output values written to the given output. For example, given the following output specification:
lambda will produce 6 (3 * 2) index values and 2 output values for arr1, and 2 (2 * 1) index values and 1 output value for arr2. Additionally, the results are grouped, so the first 6 index values will correspond to the first two output values, and so on. For this example, lambda should return a total of 11 values, 8 index values and 3 output values. |
Hist SubExp [HistOp lore] (Lambda lore) [VName] | Hist length dest-arrays-and-ops fun arrays The first SubExp is the length of the input arrays. The first
list describes the operations to perform. The |
Screma SubExp [VName] (ScremaForm lore) | A combination of scan, reduction, and map. The first
|
Instances
Is the stream chunk required to correspond to a contiguous
subsequence of the original input (InOrder
) or not? Disorder
streams can be more efficient, but not all algorithms work with
this.
data StreamForm lore Source #
What kind of stream is this?
Instances
Decorations lore => Eq (StreamForm lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC (==) :: StreamForm lore -> StreamForm lore -> Bool # (/=) :: StreamForm lore -> StreamForm lore -> Bool # | |
Decorations lore => Ord (StreamForm lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC compare :: StreamForm lore -> StreamForm lore -> Ordering # (<) :: StreamForm lore -> StreamForm lore -> Bool # (<=) :: StreamForm lore -> StreamForm lore -> Bool # (>) :: StreamForm lore -> StreamForm lore -> Bool # (>=) :: StreamForm lore -> StreamForm lore -> Bool # max :: StreamForm lore -> StreamForm lore -> StreamForm lore # min :: StreamForm lore -> StreamForm lore -> StreamForm lore # | |
Decorations lore => Show (StreamForm lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC showsPrec :: Int -> StreamForm lore -> ShowS # show :: StreamForm lore -> String # showList :: [StreamForm lore] -> ShowS # |
data ScremaForm lore Source #
The essential parts of a Screma
factored out (everything
except the input arrays).
ScremaForm [Scan lore] [Reduce lore] (Lambda lore) |
Instances
Decorations lore => Eq (ScremaForm lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC (==) :: ScremaForm lore -> ScremaForm lore -> Bool # (/=) :: ScremaForm lore -> ScremaForm lore -> Bool # | |
Decorations lore => Ord (ScremaForm lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC compare :: ScremaForm lore -> ScremaForm lore -> Ordering # (<) :: ScremaForm lore -> ScremaForm lore -> Bool # (<=) :: ScremaForm lore -> ScremaForm lore -> Bool # (>) :: ScremaForm lore -> ScremaForm lore -> Bool # (>=) :: ScremaForm lore -> ScremaForm lore -> Bool # max :: ScremaForm lore -> ScremaForm lore -> ScremaForm lore # min :: ScremaForm lore -> ScremaForm lore -> ScremaForm lore # | |
Decorations lore => Show (ScremaForm lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC showsPrec :: Int -> ScremaForm lore -> ShowS # show :: ScremaForm lore -> String # showList :: [ScremaForm lore] -> ShowS # |
Information about computing a single histogram.
HistOp | |
|
Instances
Decorations lore => Eq (HistOp lore) Source # | |
Decorations lore => Ord (HistOp lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC | |
Decorations lore => Show (HistOp lore) Source # | |
How to compute a single scan result.
Scan | |
|
Instances
Decorations lore => Eq (Scan lore) Source # | |
Decorations lore => Ord (Scan lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC | |
Decorations lore => Show (Scan lore) Source # | |
PrettyLore lore => Pretty (Scan lore) Source # | |
singleScan :: Bindable lore => [Scan lore] -> Scan lore Source #
Combine multiple scan operators to a single operator.
How to compute a single reduction result.
Reduce | |
|
Instances
Decorations lore => Eq (Reduce lore) Source # | |
Decorations lore => Ord (Reduce lore) Source # | |
Defined in Futhark.IR.SOACS.SOAC | |
Decorations lore => Show (Reduce lore) Source # | |
PrettyLore lore => Pretty (Reduce lore) Source # | |
redResults :: [Reduce lore] -> Int Source #
How many reduction results are produced by these Reduce
s?
singleReduce :: Bindable lore => [Reduce lore] -> Reduce lore Source #
Combine multiple reduction operators to a single operator.
Utility
scremaType :: SubExp -> ScremaForm lore -> [Type] Source #
The types produced by a single Screma
, given the size of the
input array.
mkIdentityLambda :: (Bindable lore, MonadFreshNames m) => [Type] -> m (Lambda lore) Source #
Construct a lambda that takes parameters of the given types and simply returns them unchanged.
isIdentityLambda :: Lambda lore -> Bool Source #
Is the given lambda an identity lambda?
scanomapSOAC :: [Scan lore] -> Lambda lore -> ScremaForm lore Source #
Construct a Screma with possibly multiple scans, and the given map function.
redomapSOAC :: [Reduce lore] -> Lambda lore -> ScremaForm lore Source #
Construct a Screma with possibly multiple reductions, and the given map function.
scanSOAC :: (Bindable lore, MonadFreshNames m) => [Scan lore] -> m (ScremaForm lore) Source #
Construct a Screma with possibly multiple scans, and identity map function.
reduceSOAC :: (Bindable lore, MonadFreshNames m) => [Reduce lore] -> m (ScremaForm lore) Source #
Construct a Screma with possibly multiple reductions, and identity map function.
mapSOAC :: Lambda lore -> ScremaForm lore Source #
Construct a Screma corresponding to a map.
isScanomapSOAC :: ScremaForm lore -> Maybe ([Scan lore], Lambda lore) Source #
Does this Screma correspond to a scan-map composition?
isRedomapSOAC :: ScremaForm lore -> Maybe ([Reduce lore], Lambda lore) Source #
Does this Screma correspond to a reduce-map composition?
isScanSOAC :: ScremaForm lore -> Maybe [Scan lore] Source #
Does this Screma correspond to pure scan?
isReduceSOAC :: ScremaForm lore -> Maybe [Reduce lore] Source #
Does this Screma correspond to a pure reduce?
isMapSOAC :: ScremaForm lore -> Maybe (Lambda lore) Source #
Does this Screma correspond to a simple map, without any reduction or scan results?
ppScrema :: (PrettyLore lore, Pretty inp) => SubExp -> [inp] -> ScremaForm lore -> Doc Source #
Prettyprint the given Screma.
ppHist :: (PrettyLore lore, Pretty inp) => SubExp -> [HistOp lore] -> Lambda lore -> [inp] -> Doc Source #
Prettyprint the given histogram operation.
groupScatterResults :: [(Shape, Int, array)] -> [a] -> [(Shape, array, [([a], a)])] Source #
groupScatterResults specification results
Groups the index values and result values of results according to the specification.
This function is used for extracting and grouping the results of a
scatter. In the SOAC representation, the lambda inside a Scatter
returns
all indices and values as one big list. This function groups each value with
its corresponding indices (as determined by the Shape
of the output array).
The elements of the resulting list correspond to the shape and name of the output parameters, in addition to a list of values written to that output parameter, along with the array indices marking where to write them to.
See Scatter
for more information.
groupScatterResults' :: [(Shape, Int, array)] -> [a] -> [([a], a)] Source #
groupScatterResults' specification results
Groups the index values and result values of results according to the
output specification. This is the simpler version of groupScatterResults
,
which doesn't return any information about shapes or output arrays.
See groupScatterResults
for more information,
splitScatterResults :: [(Shape, Int, array)] -> [a] -> ([a], [a]) Source #
splitScatterResults specification results
Splits the results array into indices and values according to the output specification.
See groupScatterResults
for more information.
Generic traversal
data SOACMapper flore tlore m Source #
SOACMapper | |
|
identitySOACMapper :: Monad m => SOACMapper lore lore m Source #
A mapper that simply returns the SOAC verbatim.
mapSOACM :: (Applicative m, Monad m) => SOACMapper flore tlore m -> SOAC flore -> m (SOAC tlore) Source #
Map a monadic action across the immediate children of a SOAC. The mapping does not descend recursively into subexpressions and is done left-to-right.