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

Futhark.Analysis.HORep.SOAC

Description

High-level representation of SOACs. When performing SOAC-transformations, operating on normal Exp values is somewhat of a nuisance, as they can represent terms that are not proper SOACs. In contrast, this module exposes a SOAC representation that does not enable invalid representations (except for type errors).

Furthermore, while standard normalised Futhark requires that the inputs to a SOAC are variables or constants, the representation in this module also supports various index-space transformations, like replicate or rearrange. This is also very convenient when implementing transformations.

The names exported by this module conflict with the standard Futhark syntax tree constructors, so you are advised to use a qualified import:

import Futhark.Analysis.HORep.SOAC (SOAC)
import qualified Futhark.Analysis.HORep.SOAC as SOAC
Synopsis

SOACs

data SOAC lore Source #

A definite representation of a SOAC expression.

Constructors

Stream SubExp (StreamForm lore) (Lambda lore) [SubExp] [Input] 
Scatter SubExp (Lambda lore) [Input] [(Shape, Int, VName)] 
Screma SubExp (ScremaForm lore) [Input] 
Hist SubExp [HistOp lore] (Lambda lore) [Input] 

Instances

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

Defined in Futhark.Analysis.HORep.SOAC

Methods

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

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

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

Defined in Futhark.Analysis.HORep.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.Analysis.HORep.SOAC

Methods

ppr :: SOAC lore -> Doc #

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

pprList :: [SOAC lore] -> Doc #

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 #

inputs :: SOAC lore -> [Input] Source #

Returns the inputs used in a SOAC.

setInputs :: [Input] -> SOAC lore -> SOAC lore Source #

Set the inputs to a SOAC.

lambda :: SOAC lore -> Lambda lore Source #

The lambda used in a given SOAC.

setLambda :: Lambda lore -> SOAC lore -> SOAC lore Source #

Set the lambda used in the SOAC.

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

The return type of a SOAC.

width :: SOAC lore -> SubExp Source #

The "width" of a SOAC is the expected outer size of its array inputs _after_ input-transforms have been carried out.

Converting to and from expressions

data NotSOAC Source #

The reason why some expression cannot be converted to a SOAC value.

Constructors

NotSOAC

The expression is not a (tuple-)SOAC at all.

Instances

Instances details
Show NotSOAC Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

fromExp :: (Op lore ~ SOAC lore, HasScope lore m) => Exp lore -> m (Either NotSOAC (SOAC lore)) Source #

Either convert an expression to the normalised SOAC representation, or a reason why the expression does not have the valid form.

toExp :: (MonadBinder m, Op (Lore m) ~ SOAC (Lore m)) => SOAC (Lore m) -> m (Exp (Lore m)) Source #

Convert a SOAC to the corresponding expression.

toSOAC :: MonadBinder m => SOAC (Lore m) -> m (SOAC (Lore m)) Source #

Convert a SOAC to a Futhark-level SOAC.

SOAC inputs

data Input Source #

One array input to a SOAC - a SOAC may have multiple inputs, but all are of this form. Only the array inputs are expressed with this type; other arguments, such as initial accumulator values, are plain expressions. The transforms are done left-to-right, that is, the first element of the ArrayTransform list is applied first.

Instances

Instances details
Eq Input Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

(==) :: Input -> Input -> Bool #

(/=) :: Input -> Input -> Bool #

Ord Input Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

compare :: Input -> Input -> Ordering #

(<) :: Input -> Input -> Bool #

(<=) :: Input -> Input -> Bool #

(>) :: Input -> Input -> Bool #

(>=) :: Input -> Input -> Bool #

max :: Input -> Input -> Input #

min :: Input -> Input -> Input #

Show Input Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

Pretty Input Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Methods

ppr :: Input -> Doc #

pprPrec :: Int -> Input -> Doc #

pprList :: [Input] -> Doc #

Substitute Input Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

varInput :: HasScope t f => VName -> f Input Source #

Create a plain array variable input with no transformations.

identInput :: Ident -> Input Source #

Create a plain array variable input with no transformations, from an Ident.

isVarInput :: Input -> Maybe VName Source #

If the given input is a plain variable input, with no transforms, return the variable.

isVarishInput :: Input -> Maybe VName Source #

If the given input is a plain variable input, with no non-vacuous transforms, return the variable.

addTransform :: ArrayTransform -> Input -> Input Source #

Add a transformation to the end of the transformation list.

addInitialTransforms :: ArrayTransforms -> Input -> Input Source #

Add several transformations to the start of the transformation list.

inputArray :: Input -> VName Source #

Return the array name of the input.

inputRank :: Input -> Int Source #

Return the array rank (dimensionality) of an input. Just a convenient alias.

inputType :: Input -> Type Source #

Return the type of an input.

inputRowType :: Input -> Type Source #

Return the row type of an input. Just a convenient alias.

transformRows :: ArrayTransforms -> Input -> Input Source #

Apply the transformations to every row of the input.

transposeInput :: Int -> Int -> Input -> Input Source #

Add to the input a Rearrange transform that performs an (k,n) transposition. The new transform will be at the end of the current transformation list.

Input transformations

data ArrayTransforms Source #

A sequence of array transformations, heavily inspired by Data.Seq. You can decompose it using viewf and viewl, and grow it by using |> and <|. These correspond closely to the similar operations for sequences, except that appending will try to normalise and simplify the transformation sequence.

The data type is opaque in order to enforce normalisation invariants. Basically, when you grow the sequence, the implementation will try to coalesce neighboring permutations, for example by composing permutations and removing identity transformations.

Instances

Instances details
Eq ArrayTransforms Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Ord ArrayTransforms Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Show ArrayTransforms Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Semigroup ArrayTransforms Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Monoid ArrayTransforms Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

Substitute ArrayTransforms Source # 
Instance details

Defined in Futhark.Analysis.HORep.SOAC

noTransforms :: ArrayTransforms Source #

The empty transformation list.

nullTransforms :: ArrayTransforms -> Bool Source #

Is it an empty transformation list?

(|>) :: ArrayTransforms -> ArrayTransform -> ArrayTransforms Source #

Add a transform to the end of the transformation list.

(<|) :: ArrayTransform -> ArrayTransforms -> ArrayTransforms Source #

Add a transform at the beginning of the transformation list.

viewf :: ArrayTransforms -> ViewF Source #

Decompose the input-end of the transformation sequence.

data ViewF Source #

A view of the first transformation to be applied.

viewl :: ArrayTransforms -> ViewL Source #

Decompose the output-end of the transformation sequence.

data ViewL Source #

A view of the last transformation to be applied.

data ArrayTransform Source #

A single, simple transformation. If you want several, don't just create a list, use ArrayTransforms instead.

Constructors

Rearrange Certificates [Int]

A permutation of an otherwise valid input.

Reshape Certificates (ShapeChange SubExp)

A reshaping of an otherwise valid input.

ReshapeOuter Certificates (ShapeChange SubExp)

A reshaping of the outer dimension.

ReshapeInner Certificates (ShapeChange SubExp)

A reshaping of everything but the outer dimension.

Replicate Certificates Shape

Replicate the rows of the array a number of times.

transformFromExp :: Certificates -> Exp lore -> Maybe (VName, ArrayTransform) Source #

Given an expression, determine whether the expression represents an input transformation of an array variable. If so, return the variable and the transformation. Only Rearrange and Reshape are possible to express this way.

soacToStream :: (MonadFreshNames m, Bindable lore, Op lore ~ SOAC lore) => SOAC lore -> m (SOAC lore, [Ident]) Source #

To-Stream translation of SOACs. Returns the Stream SOAC and the extra-accumulator body-result ident if any.