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 rep
- data StreamOrd
- data StreamForm rep
- = Parallel StreamOrd Commutativity (Lambda rep)
- | Sequential
- data ScremaForm rep = ScremaForm [Scan rep] [Reduce rep] (Lambda rep)
- data HistOp rep = HistOp {
- histWidth :: SubExp
- histRaceFactor :: SubExp
- histDest :: [VName]
- histNeutral :: [SubExp]
- histOp :: Lambda rep
- data Scan rep = Scan {
- scanLambda :: Lambda rep
- scanNeutral :: [SubExp]
- scanResults :: [Scan rep] -> Int
- singleScan :: Buildable rep => [Scan rep] -> Scan rep
- data Reduce rep = Reduce {
- redComm :: Commutativity
- redLambda :: Lambda rep
- redNeutral :: [SubExp]
- redResults :: [Reduce rep] -> Int
- singleReduce :: Buildable rep => [Reduce rep] -> Reduce rep
- scremaType :: SubExp -> ScremaForm rep -> [Type]
- soacType :: SOAC rep -> [Type]
- typeCheckSOAC :: Checkable rep => SOAC (Aliases rep) -> TypeM rep ()
- mkIdentityLambda :: (Buildable rep, MonadFreshNames m) => [Type] -> m (Lambda rep)
- isIdentityLambda :: Lambda rep -> Bool
- nilFn :: Buildable rep => Lambda rep
- scanomapSOAC :: [Scan rep] -> Lambda rep -> ScremaForm rep
- redomapSOAC :: [Reduce rep] -> Lambda rep -> ScremaForm rep
- scanSOAC :: (Buildable rep, MonadFreshNames m) => [Scan rep] -> m (ScremaForm rep)
- reduceSOAC :: (Buildable rep, MonadFreshNames m) => [Reduce rep] -> m (ScremaForm rep)
- mapSOAC :: Lambda rep -> ScremaForm rep
- isScanomapSOAC :: ScremaForm rep -> Maybe ([Scan rep], Lambda rep)
- isRedomapSOAC :: ScremaForm rep -> Maybe ([Reduce rep], Lambda rep)
- isScanSOAC :: ScremaForm rep -> Maybe [Scan rep]
- isReduceSOAC :: ScremaForm rep -> Maybe [Reduce rep]
- isMapSOAC :: ScremaForm rep -> Maybe (Lambda rep)
- ppScrema :: (PrettyRep rep, Pretty inp) => SubExp -> [inp] -> ScremaForm rep -> Doc
- ppHist :: (PrettyRep rep, Pretty inp) => SubExp -> [HistOp rep] -> Lambda rep -> [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 frep trep m = SOACMapper {
- mapOnSOACSubExp :: SubExp -> m SubExp
- mapOnSOACLambda :: Lambda frep -> m (Lambda trep)
- mapOnSOACVName :: VName -> m VName
- identitySOACMapper :: Monad m => SOACMapper rep rep m
- mapSOACM :: (Applicative m, Monad m) => SOACMapper frep trep m -> SOAC frep -> m (SOAC trep)
Documentation
A second-order array combinator (SOAC).
Stream SubExp [VName] (StreamForm rep) [SubExp] (Lambda rep) | |
Scatter SubExp (Lambda rep) [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 rep] (Lambda rep) [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 rep) | 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 rep Source #
What kind of stream is this?
Instances
RepTypes rep => Eq (StreamForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC (==) :: StreamForm rep -> StreamForm rep -> Bool # (/=) :: StreamForm rep -> StreamForm rep -> Bool # | |
RepTypes rep => Ord (StreamForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC compare :: StreamForm rep -> StreamForm rep -> Ordering # (<) :: StreamForm rep -> StreamForm rep -> Bool # (<=) :: StreamForm rep -> StreamForm rep -> Bool # (>) :: StreamForm rep -> StreamForm rep -> Bool # (>=) :: StreamForm rep -> StreamForm rep -> Bool # max :: StreamForm rep -> StreamForm rep -> StreamForm rep # min :: StreamForm rep -> StreamForm rep -> StreamForm rep # | |
RepTypes rep => Show (StreamForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC showsPrec :: Int -> StreamForm rep -> ShowS # show :: StreamForm rep -> String # showList :: [StreamForm rep] -> ShowS # |
data ScremaForm rep Source #
The essential parts of a Screma
factored out (everything
except the input arrays).
ScremaForm [Scan rep] [Reduce rep] (Lambda rep) |
Instances
RepTypes rep => Eq (ScremaForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC (==) :: ScremaForm rep -> ScremaForm rep -> Bool # (/=) :: ScremaForm rep -> ScremaForm rep -> Bool # | |
RepTypes rep => Ord (ScremaForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC compare :: ScremaForm rep -> ScremaForm rep -> Ordering # (<) :: ScremaForm rep -> ScremaForm rep -> Bool # (<=) :: ScremaForm rep -> ScremaForm rep -> Bool # (>) :: ScremaForm rep -> ScremaForm rep -> Bool # (>=) :: ScremaForm rep -> ScremaForm rep -> Bool # max :: ScremaForm rep -> ScremaForm rep -> ScremaForm rep # min :: ScremaForm rep -> ScremaForm rep -> ScremaForm rep # | |
RepTypes rep => Show (ScremaForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC showsPrec :: Int -> ScremaForm rep -> ShowS # show :: ScremaForm rep -> String # showList :: [ScremaForm rep] -> ShowS # |
Information about computing a single histogram.
HistOp | |
|
Instances
RepTypes rep => Eq (HistOp rep) Source # | |
RepTypes rep => Ord (HistOp rep) Source # | |
RepTypes rep => Show (HistOp rep) Source # | |
How to compute a single scan result.
Scan | |
|
singleScan :: Buildable rep => [Scan rep] -> Scan rep Source #
Combine multiple scan operators to a single operator.
How to compute a single reduction result.
Reduce | |
|
Instances
RepTypes rep => Eq (Reduce rep) Source # | |
RepTypes rep => Ord (Reduce rep) Source # | |
RepTypes rep => Show (Reduce rep) Source # | |
PrettyRep rep => Pretty (Reduce rep) Source # | |
singleReduce :: Buildable rep => [Reduce rep] -> Reduce rep Source #
Combine multiple reduction operators to a single operator.
Utility
scremaType :: SubExp -> ScremaForm rep -> [Type] Source #
The types produced by a single Screma
, given the size of the
input array.
mkIdentityLambda :: (Buildable rep, MonadFreshNames m) => [Type] -> m (Lambda rep) Source #
Construct a lambda that takes parameters of the given types and simply returns them unchanged.
isIdentityLambda :: Lambda rep -> Bool Source #
Is the given lambda an identity lambda?
scanomapSOAC :: [Scan rep] -> Lambda rep -> ScremaForm rep Source #
Construct a Screma with possibly multiple scans, and the given map function.
redomapSOAC :: [Reduce rep] -> Lambda rep -> ScremaForm rep Source #
Construct a Screma with possibly multiple reductions, and the given map function.
scanSOAC :: (Buildable rep, MonadFreshNames m) => [Scan rep] -> m (ScremaForm rep) Source #
Construct a Screma with possibly multiple scans, and identity map function.
reduceSOAC :: (Buildable rep, MonadFreshNames m) => [Reduce rep] -> m (ScremaForm rep) Source #
Construct a Screma with possibly multiple reductions, and identity map function.
mapSOAC :: Lambda rep -> ScremaForm rep Source #
Construct a Screma corresponding to a map.
isScanomapSOAC :: ScremaForm rep -> Maybe ([Scan rep], Lambda rep) Source #
Does this Screma correspond to a scan-map composition?
isRedomapSOAC :: ScremaForm rep -> Maybe ([Reduce rep], Lambda rep) Source #
Does this Screma correspond to a reduce-map composition?
isScanSOAC :: ScremaForm rep -> Maybe [Scan rep] Source #
Does this Screma correspond to pure scan?
isReduceSOAC :: ScremaForm rep -> Maybe [Reduce rep] Source #
Does this Screma correspond to a pure reduce?
isMapSOAC :: ScremaForm rep -> Maybe (Lambda rep) Source #
Does this Screma correspond to a simple map, without any reduction or scan results?
ppScrema :: (PrettyRep rep, Pretty inp) => SubExp -> [inp] -> ScremaForm rep -> Doc Source #
Prettyprint the given Screma.
ppHist :: (PrettyRep rep, Pretty inp) => SubExp -> [HistOp rep] -> Lambda rep -> [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 frep trep m Source #
SOACMapper | |
|
identitySOACMapper :: Monad m => SOACMapper rep rep m Source #
A mapper that simply returns the SOAC verbatim.
mapSOACM :: (Applicative m, Monad m) => SOACMapper frep trep m -> SOAC frep -> m (SOAC trep) 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.