futhark-0.21.3: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.IR.MC

Description

A representation for multicore CPU parallelism.

Synopsis

Documentation

data MC Source #

Instances

Instances details
RepTypes MC Source # 
Instance details

Defined in Futhark.IR.MC

PrettyRep MC Source # 
Instance details

Defined in Futhark.IR.MC

Methods

ppExpDec :: ExpDec MC -> Exp MC -> Maybe Doc Source #

ASTRep MC Source # 
Instance details

Defined in Futhark.IR.MC

Methods

expTypesFromPat :: (HasScope MC m, Monad m) => Pat MC -> m [BranchType MC] Source #

Buildable MC Source # 
Instance details

Defined in Futhark.IR.MC

BuilderOps MC Source # 
Instance details

Defined in Futhark.IR.MC

Methods

mkExpDecB :: (MonadBuilder m, Rep m ~ MC) => Pat MC -> Exp MC -> m (ExpDec MC) Source #

mkBodyB :: (MonadBuilder m, Rep m ~ MC) => Stms MC -> Result -> m (Body MC) Source #

mkLetNamesB :: (MonadBuilder m, Rep m ~ MC) => [VName] -> Exp MC -> m (Stm MC) Source #

Checkable MC Source # 
Instance details

Defined in Futhark.IR.MC

CheckableOp MC Source # 
Instance details

Defined in Futhark.IR.MC

HasSegOp MC Source # 
Instance details

Defined in Futhark.IR.MC

Associated Types

type SegOpLevel MC Source #

TraverseOpStms (Wise MC) Source # 
Instance details

Defined in Futhark.IR.MC

BuilderOps (Wise MC) Source # 
Instance details

Defined in Futhark.IR.MC

Methods

mkExpDecB :: (MonadBuilder m, Rep m ~ Wise MC) => Pat (Wise MC) -> Exp (Wise MC) -> m (ExpDec (Wise MC)) Source #

mkBodyB :: (MonadBuilder m, Rep m ~ Wise MC) => Stms (Wise MC) -> Result -> m (Body (Wise MC)) Source #

mkLetNamesB :: (MonadBuilder m, Rep m ~ Wise MC) => [VName] -> Exp (Wise MC) -> m (Stm (Wise MC)) Source #

HasSegOp (Wise MC) Source # 
Instance details

Defined in Futhark.IR.MC

Associated Types

type SegOpLevel (Wise MC) Source #

type LetDec MC Source # 
Instance details

Defined in Futhark.IR.MC

type LetDec MC = Type
type ExpDec MC Source # 
Instance details

Defined in Futhark.IR.MC

type ExpDec MC = ()
type BodyDec MC Source # 
Instance details

Defined in Futhark.IR.MC

type BodyDec MC = ()
type FParamInfo MC Source # 
Instance details

Defined in Futhark.IR.MC

type LParamInfo MC Source # 
Instance details

Defined in Futhark.IR.MC

type RetType MC Source # 
Instance details

Defined in Futhark.IR.MC

type BranchType MC Source # 
Instance details

Defined in Futhark.IR.MC

type Op MC Source # 
Instance details

Defined in Futhark.IR.MC

type Op MC = MCOp MC (SOAC MC)
type SegOpLevel MC Source # 
Instance details

Defined in Futhark.IR.MC

type SegOpLevel MC = ()
type SegOpLevel (Wise MC) Source # 
Instance details

Defined in Futhark.IR.MC

type SegOpLevel (Wise MC) = ()

Simplification

Module re-exports

data SOACMapper frep trep m Source #

Like Mapper, but just for SOACs.

Constructors

SOACMapper 

Fields

data Reduce rep Source #

How to compute a single reduction result.

Constructors

Reduce 

Instances

Instances details
RepTypes rep => Eq (Reduce rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

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

RepTypes rep => Ord (Reduce rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: Reduce rep -> Reduce rep -> Ordering #

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

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

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

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

max :: Reduce rep -> Reduce rep -> Reduce rep #

min :: Reduce rep -> Reduce rep -> Reduce rep #

RepTypes rep => Show (Reduce rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

show :: Reduce rep -> String #

showList :: [Reduce rep] -> ShowS #

PrettyRep rep => Pretty (Reduce rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

ppr :: Reduce rep -> Doc #

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

pprList :: [Reduce rep] -> Doc #

data Scan rep Source #

How to compute a single scan result.

Constructors

Scan 

Fields

Instances

Instances details
RepTypes rep => Eq (Scan rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

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

RepTypes rep => Ord (Scan rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: Scan rep -> Scan rep -> Ordering #

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

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

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

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

max :: Scan rep -> Scan rep -> Scan rep #

min :: Scan rep -> Scan rep -> Scan rep #

RepTypes rep => Show (Scan rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

show :: Scan rep -> String #

showList :: [Scan rep] -> ShowS #

PrettyRep rep => Pretty (Scan rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

ppr :: Scan rep -> Doc #

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

pprList :: [Scan rep] -> Doc #

data ScremaForm rep Source #

The essential parts of a Screma factored out (everything except the input arrays).

Constructors

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

Instances

Instances details
RepTypes rep => Eq (ScremaForm rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

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

RepTypes rep => Ord (ScremaForm rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

Defined in Futhark.IR.SOACS.SOAC

Methods

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

show :: ScremaForm rep -> String #

showList :: [ScremaForm rep] -> ShowS #

data StreamForm rep Source #

What kind of stream is this?

Instances

Instances details
RepTypes rep => Eq (StreamForm rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

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

RepTypes rep => Ord (StreamForm rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

Defined in Futhark.IR.SOACS.SOAC

Methods

showsPrec :: Int -> StreamForm rep -> ShowS #

show :: StreamForm rep -> String #

showList :: [StreamForm rep] -> ShowS #

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 SOAC rep Source #

A second-order array combinator (SOAC).

Constructors

Stream SubExp [VName] (StreamForm rep) [SubExp] (Lambda rep) 
Scatter SubExp [VName] (Lambda rep) [(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 [VName] [HistOp rep] (Lambda rep)
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 rep)

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

Instances

Instances details
RepTypes rep => Eq (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

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

RepTypes rep => Ord (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

compare :: SOAC rep -> SOAC rep -> Ordering #

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

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

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

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

max :: SOAC rep -> SOAC rep -> SOAC rep #

min :: SOAC rep -> SOAC rep -> SOAC rep #

RepTypes rep => Show (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

show :: SOAC rep -> String #

showList :: [SOAC rep] -> ShowS #

PrettyRep rep => Pretty (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

ppr :: SOAC rep -> Doc #

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

pprList :: [SOAC rep] -> Doc #

TypedOp (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

ASTRep rep => FreeIn (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

freeIn' :: SOAC rep -> FV Source #

ASTRep rep => Substitute (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

ASTRep rep => Rename (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

ASTRep rep => IsOp (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

safeOp :: SOAC rep -> Bool Source #

cheapOp :: SOAC rep -> Bool Source #

(ASTRep rep, ASTRep (Aliases rep), CanBeAliased (Op rep)) => CanBeAliased (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Associated Types

type OpWithAliases (SOAC rep) Source #

(ASTRep rep, Aliased rep) => AliasedOp (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

consumedInOp :: SOAC rep -> Names Source #

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

Defined in Futhark.IR.SOACS.SOAC

Methods

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

(ASTRep rep, CanBeWise (Op rep)) => CanBeWise (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Associated Types

type OpWithWisdom (SOAC rep) Source #

RepTypes rep => IndexOp (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

indexOp :: (ASTRep rep0, IndexOp (Op rep0)) => SymbolTable rep0 -> Int -> SOAC rep -> [TPrimExp Int64 VName] -> Maybe Indexed Source #

(ASTRep rep, CanBeAliased (Op rep), CSEInOp (OpWithAliases (Op rep))) => CSEInOp (SOAC (Aliases rep)) Source # 
Instance details

Defined in Futhark.Optimise.CSE

Methods

cseInOp :: SOAC (Aliases rep) -> CSEM rep0 (SOAC (Aliases rep))

type OpWithAliases (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

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

Defined in Futhark.IR.SOACS.SOAC

type OpWithWisdom (SOAC rep) = SOAC (Wise rep)

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

How many reduction results are produced by these Scans?

singleScan :: Buildable rep => [Scan rep] -> Scan rep Source #

Combine multiple scan operators to a single operator.

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

How many reduction results are produced by these Reduces?

singleReduce :: Buildable rep => [Reduce rep] -> Reduce rep Source #

Combine multiple reduction operators to a single operator.

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?

nilFn :: Buildable rep => Lambda rep Source #

A lambda with no parameters that returns no values.

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?

isScanSOAC :: ScremaForm rep -> Maybe [Scan rep] Source #

Does this Screma correspond to pure scan?

isRedomapSOAC :: ScremaForm rep -> Maybe ([Reduce rep], Lambda rep) Source #

Does this Screma correspond to a reduce-map composition?

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?

scremaLambda :: ScremaForm rep -> Lambda rep Source #

Return the "main" lambda of the Screma. For a map, this is equivalent to isMapSOAC. Note that the meaning of the return value of this lambda depends crucially on exactly which Screma this is. The parameters will correspond exactly to elements of the input arrays, however.

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.

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.

traverseSOACStms :: Monad m => OpStmsTraverser m (SOAC rep) rep Source #

A helper for defining TraverseOpStms.

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

The type of a SOAC.

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

Type-check a SOAC.

ppScrema :: (PrettyRep rep, Pretty inp) => SubExp -> [inp] -> ScremaForm rep -> Doc Source #

Prettyprint the given Screma.

ppHist :: (PrettyRep rep, Pretty inp) => SubExp -> [inp] -> [HistOp rep] -> Lambda rep -> Doc Source #

Prettyprint the given histogram operation.