| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
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
- data SOAC rep
- data ScremaForm rep = ScremaForm {
- scremaLambda :: Lambda rep
- scremaScans :: [Scan rep]
- scremaReduces :: [Reduce rep]
- inputs :: SOAC rep -> [Input]
- setInputs :: [Input] -> SOAC rep -> SOAC rep
- lambda :: SOAC rep -> Lambda rep
- setLambda :: Lambda rep -> SOAC rep -> SOAC rep
- typeOf :: SOAC rep -> [Type]
- width :: SOAC rep -> SubExp
- data NotSOAC = NotSOAC
- fromExp :: (Op rep ~ SOAC rep, HasScope rep m) => Exp rep -> m (Either NotSOAC (SOAC rep))
- toExp :: (MonadBuilder m, Op (Rep m) ~ SOAC (Rep m)) => SOAC (Rep m) -> m (Exp (Rep m))
- toSOAC :: MonadBuilder m => SOAC (Rep m) -> m (SOAC (Rep m))
- data Input = Input ArrayTransforms VName Type
- varInput :: HasScope t f => VName -> f Input
- inputTransforms :: Input -> ArrayTransforms
- identInput :: Ident -> Input
- isVarInput :: Input -> Maybe VName
- isVarishInput :: Input -> Maybe VName
- addTransform :: ArrayTransform -> Input -> Input
- addInitialTransforms :: ArrayTransforms -> Input -> Input
- inputArray :: Input -> VName
- inputRank :: Input -> Int
- inputType :: Input -> Type
- inputRowType :: Input -> Type
- transformRows :: ArrayTransforms -> Input -> Input
- transposeInput :: Int -> Int -> Input -> Input
- applyTransforms :: MonadBuilder m => ArrayTransforms -> VName -> m VName
- data ArrayTransforms
- noTransforms :: ArrayTransforms
- nullTransforms :: ArrayTransforms -> Bool
- (|>) :: ArrayTransforms -> ArrayTransform -> ArrayTransforms
- (<|) :: ArrayTransform -> ArrayTransforms -> ArrayTransforms
- viewf :: ArrayTransforms -> ViewF
- data ViewF
- viewl :: ArrayTransforms -> ViewL
- data ViewL
- data ArrayTransform
- transformFromExp :: StmAux () -> Exp rep -> Maybe (VName, ArrayTransform)
- transformToExp :: (Monad m, HasScope rep m) => ArrayTransform -> VName -> m (StmAux (), Exp rep)
- soacToStream :: (HasScope rep m, MonadFreshNames m, Buildable rep, BuilderOps rep, Op rep ~ SOAC rep) => SOAC rep -> m (SOAC rep, [Ident])
SOACs
A definite representation of a SOAC expression.
Constructors
| Stream SubExp [Input] [SubExp] (Lambda rep) | |
| Screma SubExp [Input] (ScremaForm rep) | |
| Hist SubExp [Input] [HistOp rep] (Lambda rep) |
data ScremaForm rep Source #
The essential parts of a Screma factored out (everything except the input arrays).
Constructors
| ScremaForm | |
Fields
| |
Instances
| RepTypes rep => Show (ScremaForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC Methods showsPrec :: Int -> ScremaForm rep -> ShowS # show :: ScremaForm rep -> String # showList :: [ScremaForm rep] -> ShowS # | |
| ASTRep rep => FreeIn (ScremaForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC Methods freeIn' :: ScremaForm rep -> FV Source # | |
| RepTypes rep => Eq (ScremaForm rep) Source # | |
Defined in Futhark.IR.SOACS.SOAC Methods (==) :: ScremaForm rep -> ScremaForm rep -> Bool # (/=) :: ScremaForm rep -> ScremaForm rep -> Bool # | |
| RepTypes rep => Ord (ScremaForm rep) Source # | |
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 # | |
width :: SOAC rep -> 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
The reason why some expression cannot be converted to a SOAC value.
Constructors
| NotSOAC | The expression is not a (tuple-)SOAC at all. |
fromExp :: (Op rep ~ SOAC rep, HasScope rep m) => Exp rep -> m (Either NotSOAC (SOAC rep)) Source #
Either convert an expression to the normalised SOAC representation, or a reason why the expression does not have the valid form.
toExp :: (MonadBuilder m, Op (Rep m) ~ SOAC (Rep m)) => SOAC (Rep m) -> m (Exp (Rep m)) Source #
Convert a SOAC to the corresponding expression.
toSOAC :: MonadBuilder m => SOAC (Rep m) -> m (SOAC (Rep m)) Source #
Convert a SOAC to a Futhark-level SOAC.
SOAC inputs
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.
Constructors
| Input ArrayTransforms VName Type |
varInput :: HasScope t f => VName -> f Input Source #
Create a plain array variable input with no transformations.
inputTransforms :: Input -> ArrayTransforms Source #
The transformations applied to an input.
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.
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.
applyTransforms :: MonadBuilder m => ArrayTransforms -> VName -> m VName Source #
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
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.
A view of the first transformation to be applied.
Constructors
| EmptyF | |
| ArrayTransform :< ArrayTransforms |
viewl :: ArrayTransforms -> ViewL Source #
Decompose the output-end of the transformation sequence.
A view of the last transformation to be applied.
Constructors
| EmptyL | |
| ArrayTransforms :> ArrayTransform |
data ArrayTransform Source #
A single, simple transformation. If you want several, don't just create a list, use ArrayTransforms instead.
Constructors
| Rearrange (StmAux ()) [Int] | A permutation of an otherwise valid input. |
| Reshape (StmAux ()) (NewShape SubExp) | A reshaping of an otherwise valid input. |
| Replicate (StmAux ()) Shape | Replicate the rows of the array a number of times. |
| Index (StmAux ()) (Slice SubExp) | An array indexing operation. |
Instances
transformFromExp :: StmAux () -> Exp rep -> Maybe (VName, ArrayTransform) Source #
transformToExp :: (Monad m, HasScope rep m) => ArrayTransform -> VName -> m (StmAux (), Exp rep) Source #
Turn an array transform on an array back into an expression.
soacToStream :: (HasScope rep m, MonadFreshNames m, Buildable rep, BuilderOps rep, Op rep ~ SOAC rep) => SOAC rep -> m (SOAC rep, [Ident]) Source #
To-Stream translation of SOACs. Returns the Stream SOAC and the extra-accumulator body-result ident if any.