futhark-0.19.4: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.IR.SOACS.SOAC

Description

Definition of Second-Order Array Combinators (SOACs), which are the main form of parallelism in the early stages of the compiler.

Synopsis

Documentation

data SOAC lore Source #

A second-order array combinator (SOAC).

Constructors

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:

index_0, index_1, ..., index_n, value_0, value_1, ..., value_m

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:

([x1, y1, z1
, 2, arr1), ([x2, y2], 1, arr2)]

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 Lambda is the bucket function. Finally comes the input images.

Screma SubExp [VName] (ScremaForm lore)

A combination of scan, reduction, and map. The first SubExp is the size of the input arrays.

Instances

Instances details
Decorations lore => Eq (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

(==) :: SOAC lore -> SOAC lore -> Bool #

(/=) :: SOAC lore -> SOAC lore -> Bool #

Decorations lore => Ord (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: SOAC lore -> SOAC lore -> Ordering #

(<) :: SOAC lore -> SOAC lore -> Bool #

(<=) :: SOAC lore -> SOAC lore -> Bool #

(>) :: SOAC lore -> SOAC lore -> Bool #

(>=) :: SOAC lore -> SOAC lore -> Bool #

max :: SOAC lore -> SOAC lore -> SOAC lore #

min :: SOAC lore -> SOAC lore -> SOAC lore #

Decorations lore => Show (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

showsPrec :: Int -> SOAC lore -> ShowS #

show :: SOAC lore -> String #

showList :: [SOAC lore] -> ShowS #

PrettyLore lore => Pretty (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

ppr :: SOAC lore -> Doc #

pprPrec :: Int -> SOAC lore -> Doc #

pprList :: [SOAC lore] -> Doc #

TypedOp (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

opType :: HasScope t m => SOAC lore -> m [ExtType] Source #

ASTLore lore => FreeIn (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

freeIn' :: SOAC lore -> FV Source #

ASTLore lore => Substitute (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

substituteNames :: Map VName VName -> SOAC lore -> SOAC lore Source #

ASTLore lore => Rename (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

rename :: SOAC lore -> RenameM (SOAC lore) Source #

ASTLore lore => IsOp (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

safeOp :: SOAC lore -> Bool Source #

cheapOp :: SOAC lore -> Bool Source #

(ASTLore lore, ASTLore (Aliases lore), CanBeAliased (Op lore)) => CanBeAliased (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Associated Types

type OpWithAliases (SOAC lore) Source #

(ASTLore lore, Aliased lore) => AliasedOp (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

opAliases :: SOAC lore -> [Names] Source #

consumedInOp :: SOAC lore -> Names Source #

OpMetrics (Op lore) => OpMetrics (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

opMetrics :: SOAC lore -> MetricsM () Source #

(ASTLore lore, CanBeWise (Op lore)) => CanBeWise (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Associated Types

type OpWithWisdom (SOAC lore) Source #

Methods

removeOpWisdom :: OpWithWisdom (SOAC lore) -> SOAC lore Source #

Decorations lore => IndexOp (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

indexOp :: (ASTLore lore0, IndexOp (Op lore0)) => SymbolTable lore0 -> Int -> SOAC lore -> [TPrimExp Int64 VName] -> Maybe Indexed Source #

(ASTLore lore, CanBeAliased (Op lore), CSEInOp (OpWithAliases (Op lore))) => CSEInOp (SOAC (Aliases lore)) Source # 
Instance details

Defined in Futhark.Optimise.CSE

Methods

cseInOp :: SOAC (Aliases lore) -> CSEM lore0 (SOAC (Aliases lore))

type OpWithAliases (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

type OpWithAliases (SOAC lore) = SOAC (Aliases lore)
type OpWithWisdom (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

type OpWithWisdom (SOAC lore) = SOAC (Wise lore)

data StreamOrd Source #

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.

Constructors

InOrder 
Disorder 

Instances

Instances details
Eq StreamOrd Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Ord StreamOrd Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Show StreamOrd Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

data StreamForm lore Source #

What kind of stream is this?

Instances

Instances details
Decorations lore => Eq (StreamForm lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

(==) :: StreamForm lore -> StreamForm lore -> Bool #

(/=) :: StreamForm lore -> StreamForm lore -> Bool #

Decorations lore => Ord (StreamForm lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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 # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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).

Constructors

ScremaForm [Scan lore] [Reduce lore] (Lambda lore) 

Instances

Instances details
Decorations lore => Eq (ScremaForm lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

(==) :: ScremaForm lore -> ScremaForm lore -> Bool #

(/=) :: ScremaForm lore -> ScremaForm lore -> Bool #

Decorations lore => Ord (ScremaForm lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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 # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

showsPrec :: Int -> ScremaForm lore -> ShowS #

show :: ScremaForm lore -> String #

showList :: [ScremaForm lore] -> ShowS #

data HistOp lore Source #

Information about computing a single histogram.

Constructors

HistOp 

Fields

Instances

Instances details
Decorations lore => Eq (HistOp lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

(==) :: HistOp lore -> HistOp lore -> Bool #

(/=) :: HistOp lore -> HistOp lore -> Bool #

Decorations lore => Ord (HistOp lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: HistOp lore -> HistOp lore -> Ordering #

(<) :: HistOp lore -> HistOp lore -> Bool #

(<=) :: HistOp lore -> HistOp lore -> Bool #

(>) :: HistOp lore -> HistOp lore -> Bool #

(>=) :: HistOp lore -> HistOp lore -> Bool #

max :: HistOp lore -> HistOp lore -> HistOp lore #

min :: HistOp lore -> HistOp lore -> HistOp lore #

Decorations lore => Show (HistOp lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

showsPrec :: Int -> HistOp lore -> ShowS #

show :: HistOp lore -> String #

showList :: [HistOp lore] -> ShowS #

data Scan lore Source #

How to compute a single scan result.

Constructors

Scan 

Fields

Instances

Instances details
Decorations lore => Eq (Scan lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

(==) :: Scan lore -> Scan lore -> Bool #

(/=) :: Scan lore -> Scan lore -> Bool #

Decorations lore => Ord (Scan lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: Scan lore -> Scan lore -> Ordering #

(<) :: Scan lore -> Scan lore -> Bool #

(<=) :: Scan lore -> Scan lore -> Bool #

(>) :: Scan lore -> Scan lore -> Bool #

(>=) :: Scan lore -> Scan lore -> Bool #

max :: Scan lore -> Scan lore -> Scan lore #

min :: Scan lore -> Scan lore -> Scan lore #

Decorations lore => Show (Scan lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

showsPrec :: Int -> Scan lore -> ShowS #

show :: Scan lore -> String #

showList :: [Scan lore] -> ShowS #

PrettyLore lore => Pretty (Scan lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

ppr :: Scan lore -> Doc #

pprPrec :: Int -> Scan lore -> Doc #

pprList :: [Scan lore] -> Doc #

scanResults :: [Scan lore] -> Int Source #

How many reduction results are produced by these Scans?

singleScan :: Bindable lore => [Scan lore] -> Scan lore Source #

Combine multiple scan operators to a single operator.

data Reduce lore Source #

How to compute a single reduction result.

Constructors

Reduce 

Instances

Instances details
Decorations lore => Eq (Reduce lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

(==) :: Reduce lore -> Reduce lore -> Bool #

(/=) :: Reduce lore -> Reduce lore -> Bool #

Decorations lore => Ord (Reduce lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: Reduce lore -> Reduce lore -> Ordering #

(<) :: Reduce lore -> Reduce lore -> Bool #

(<=) :: Reduce lore -> Reduce lore -> Bool #

(>) :: Reduce lore -> Reduce lore -> Bool #

(>=) :: Reduce lore -> Reduce lore -> Bool #

max :: Reduce lore -> Reduce lore -> Reduce lore #

min :: Reduce lore -> Reduce lore -> Reduce lore #

Decorations lore => Show (Reduce lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

showsPrec :: Int -> Reduce lore -> ShowS #

show :: Reduce lore -> String #

showList :: [Reduce lore] -> ShowS #

PrettyLore lore => Pretty (Reduce lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

ppr :: Reduce lore -> Doc #

pprPrec :: Int -> Reduce lore -> Doc #

pprList :: [Reduce lore] -> Doc #

redResults :: [Reduce lore] -> Int Source #

How many reduction results are produced by these Reduces?

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.

soacType :: SOAC lore -> [Type] Source #

The type of a SOAC.

typeCheckSOAC :: Checkable lore => SOAC (Aliases lore) -> TypeM lore () Source #

Type-check a SOAC.

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?

nilFn :: Bindable lore => Lambda lore Source #

A lambda with no parameters that returns no values.

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 #

Like Mapper, but just for SOACs.

Constructors

SOACMapper 

Fields

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.