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

Futhark.Construct

Description

Constructing Futhark ASTs

This module re-exports and defines a bunch of building blocks for constructing fragments of Futhark ASTs. More importantly, it also contains a basic introduction on how to use them.

The Futhark.IR.Syntax module contains the core AST definition. One important invariant is that all bound names in a Futhark program must be globally unique. In principle, you could use the facilities from Futhark.MonadFreshNames (or your own bespoke source of unique names) to manually construct expressions, statements, and entire ASTs. In practice, this would be very tedious. Instead, we have defined a collection of building blocks (centered around the MonadBuilder type class) that permits a more abstract way of generating code.

Constructing ASTs with these building blocks requires you to ensure that all free variables are in scope. See Futhark.IR.Prop.Scope.

MonadBuilder

A monad that implements MonadBuilder tracks the statements added so far, the current names in scope, and allows you to add additional statements with addStm. Any monad that implements MonadBuilder also implements the Rep type family, which indicates which rep it works with. Inside a MonadBuilder we can use collectStms to gather up the Stms added with addStm in some nested computation.

The BuilderT monad (and its convenient Builder version) provides the simplest implementation of MonadBuilder.

Higher-level building blocks

On top of the raw facilities provided by MonadBuilder, we have more convenient facilities. For example, letSubExp lets us conveniently create a Stm for an Exp that produces a single value, and returns the (fresh) name for the resulting variable:

z <- letExp "z" $ BasicOp $ BinOp (Add Int32) (Var x) (Var y)

Monadic expression builders

This module also contains "monadic expression" functions that let us build nested expressions in a "direct" style, rather than using letExp and friends to bind every sub-part first. See functions such as eIf and eBody for example. See also Futhark.Analysis.PrimExp and the ToExp type class.

Examples

The Futhark.Transform.FirstOrderTransform module is a (relatively) simple example of how to use these components. As are some of the high-level building blocks in this very module.

Synopsis

Basic building blocks

letSubExp :: MonadBuilder m => String -> Exp (Rep m) -> m SubExp Source #

letSubExp desc e binds the expression e, which must produce a single value. Returns a SubExp corresponding to the resulting value. For expressions that produce multiple values, see letTupExp.

letExp :: MonadBuilder m => String -> Exp (Rep m) -> m VName Source #

Like letSubExp, but returns a name rather than a SubExp.

letTupExp :: MonadBuilder m => String -> Exp (Rep m) -> m [VName] Source #

Like letExp, but the expression may return multiple values.

letTupExp' :: MonadBuilder m => String -> Exp (Rep m) -> m [SubExp] Source #

Like letTupExp, but returns SubExps instead of VNames.

letInPlace :: MonadBuilder m => String -> VName -> Slice SubExp -> Exp (Rep m) -> m VName Source #

Like letExp, but the VName and Slice denote an array that is Updated with the result of the expression. The name of the updated array is returned.

Monadic expression builders

eSubExp :: MonadBuilder m => SubExp -> m (Exp (Rep m)) Source #

Turn a subexpression into a monad expression. Does not actually lead to any code generation. This is supposed to be used alongside the other monadic expression functions, such as eIf.

eParam :: MonadBuilder m => Param t -> m (Exp (Rep m)) Source #

Treat a parameter as a monadic expression.

eMatch' :: (MonadBuilder m, BranchType (Rep m) ~ ExtType) => [SubExp] -> [Case (m (Body (Rep m)))] -> m (Body (Rep m)) -> MatchSort -> m (Exp (Rep m)) Source #

As eMatch, but an MatchSort can be given.

eMatch :: (MonadBuilder m, BranchType (Rep m) ~ ExtType) => [SubExp] -> [Case (m (Body (Rep m)))] -> m (Body (Rep m)) -> m (Exp (Rep m)) Source #

Construct a Match expression. The main convenience here is that the existential context of the return type is automatically deduced, and the necessary elements added to the branches.

eIf :: (MonadBuilder m, BranchType (Rep m) ~ ExtType) => m (Exp (Rep m)) -> m (Body (Rep m)) -> m (Body (Rep m)) -> m (Exp (Rep m)) Source #

Construct a Match modelling an if-expression from a monadic condition and monadic branches. eBody might be convenient for constructing the branches.

eIf' :: (MonadBuilder m, BranchType (Rep m) ~ ExtType) => m (Exp (Rep m)) -> m (Body (Rep m)) -> m (Body (Rep m)) -> MatchSort -> m (Exp (Rep m)) Source #

As eIf, but an MatchSort can be given.

eBinOp :: MonadBuilder m => BinOp -> m (Exp (Rep m)) -> m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

Construct a BinOp expression with the given operator.

eUnOp :: MonadBuilder m => UnOp -> m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

Construct a UnOp expression with the given operator.

eCmpOp :: MonadBuilder m => CmpOp -> m (Exp (Rep m)) -> m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

Construct a CmpOp expression with the given comparison.

eConvOp :: MonadBuilder m => ConvOp -> m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

Construct a ConvOp expression with the given conversion.

eSignum :: MonadBuilder m => m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

Construct a SSignum expression. Fails if the provided expression is not of integer type.

eCopy :: MonadBuilder m => m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

Construct a Copy expression.

eBody :: MonadBuilder m => [m (Exp (Rep m))] -> m (Body (Rep m)) Source #

Construct a body from expressions. If multiple expressions are provided, their results will be concatenated in order and returned as the result.

Beware: this will not produce correct code if the type of the body would be existential. That is, the type of the results being returned should be invariant to the body.

eLambda :: MonadBuilder m => Lambda (Rep m) -> [m (Exp (Rep m))] -> m [SubExpRes] Source #

Bind each lambda parameter to the result of an expression, then bind the body of the lambda. The expressions must produce only a single value each.

eBlank :: MonadBuilder m => Type -> m (Exp (Rep m)) Source #

Construct an unspecified value of the given type.

eAll :: MonadBuilder m => [SubExp] -> m (Exp (Rep m)) Source #

True if all operands are true.

eAny :: MonadBuilder m => [SubExp] -> m (Exp (Rep m)) Source #

True if any operand is true.

eDimInBounds :: MonadBuilder m => m (Exp (Rep m)) -> m (Exp (Rep m)) -> m (Exp (Rep m)) Source #

eInBoundsForDim w i produces 0 <= i < w.

eOutOfBounds :: MonadBuilder m => VName -> [m (Exp (Rep m))] -> m (Exp (Rep m)) Source #

Are these indexes out-of-bounds for the array?

Other building blocks

asIntZ :: MonadBuilder m => IntType -> SubExp -> m SubExp Source #

Zero-extend to the given integer type.

asIntS :: MonadBuilder m => IntType -> SubExp -> m SubExp Source #

Sign-extend to the given integer type.

resultBody :: Buildable rep => [SubExp] -> Body rep Source #

Conveniently construct a body that contains no bindings.

resultBodyM :: MonadBuilder m => [SubExp] -> m (Body (Rep m)) Source #

Conveniently construct a body that contains no bindings - but this time, monadically!

insertStmsM :: MonadBuilder m => m (Body (Rep m)) -> m (Body (Rep m)) Source #

Evaluate the action, producing a body, then wrap it in all the bindings it created using addStm.

buildBody :: MonadBuilder m => m (Result, a) -> m (Body (Rep m), a) Source #

Evaluate an action that produces a Result and an auxiliary value, then return the body constructed from the Result and any statements added during the action, along the auxiliary value.

buildBody_ :: MonadBuilder m => m Result -> m (Body (Rep m)) Source #

As buildBody, but there is no auxiliary value.

mapResult :: Buildable rep => (Result -> Body rep) -> Body rep -> Body rep Source #

Change that result where evaluation of the body would stop. Also change type annotations at branches.

foldBinOp :: MonadBuilder m => BinOp -> SubExp -> [SubExp] -> m (Exp (Rep m)) Source #

Apply a binary operator to several subexpressions. A left-fold.

binOpLambda :: (MonadBuilder m, Buildable (Rep m)) => BinOp -> PrimType -> m (Lambda (Rep m)) Source #

Create a two-parameter lambda whose body applies the given binary operation to its arguments. It is assumed that both argument and result types are the same. (This assumption should be fixed at some point.)

cmpOpLambda :: (MonadBuilder m, Buildable (Rep m)) => CmpOp -> m (Lambda (Rep m)) Source #

As binOpLambda, but for CmpOps.

mkLambda :: MonadBuilder m => [LParam (Rep m)] -> m Result -> m (Lambda (Rep m)) Source #

Easily construct a Lambda within a MonadBuilder. See also runLambdaBuilder.

sliceDim :: SubExp -> DimIndex SubExp Source #

Slice a full dimension of the given size.

fullSlice :: Type -> [DimIndex SubExp] -> Slice SubExp Source #

fullSlice t slice returns slice, but with DimSlices of entire dimensions appended to the full dimensionality of t. This function is used to turn incomplete indexing complete, as required by Index.

fullSliceNum :: Num d => [d] -> [DimIndex d] -> Slice d Source #

Like fullSlice, but the dimensions are simply numeric.

isFullSlice :: Shape -> Slice SubExp -> Bool Source #

Does the slice describe the full size of the array? The most obvious such slice is one that DimSlices the full span of every dimension, but also one that fixes all unit dimensions.

sliceAt :: Type -> Int -> [DimIndex SubExp] -> Slice SubExp Source #

sliceAt t n slice returns slice but with DimSlices of the outer n dimensions prepended, and as many appended as to make it a full slice. This is a generalisation of fullSlice.

Result types

instantiateShapes :: Monad m => (Int -> m SubExp) -> [TypeBase ExtShape u] -> m [TypeBase Shape u] Source #

Instantiate all existential parts dimensions of the given type, using a monadic action to create the necessary SubExps. You should call this function within some monad that allows you to collect the actions performed (say, State).

instantiateShapes' :: [VName] -> [TypeBase ExtShape u] -> [TypeBase Shape u] Source #

Like instantiateShapes, but obtains names from the provided list. If an Ext is out of bounds of this list, the function fails with error.

removeExistentials :: ExtType -> Type -> Type Source #

Remove existentials by imposing sizes from another type where needed.

Convenience

simpleMkLetNames :: (ExpDec rep ~ (), LetDec rep ~ Type, MonadFreshNames m, TypedOp (Op rep), HasScope rep m) => [VName] -> Exp rep -> m (Stm rep) Source #

Can be used as the definition of mkLetNames for a Buildable instance for simple representations.

class ToExp a where Source #

Instances of this class can be converted to Futhark expressions within a MonadBuilder.

Methods

toExp :: MonadBuilder m => a -> m (Exp (Rep m)) Source #

Instances

Instances details
ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBuilder m => SubExp -> m (Exp (Rep m)) Source #

ToExp VName Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBuilder m => VName -> m (Exp (Rep m)) Source #

ToExp v => ToExp (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp.Convert

Methods

toExp :: MonadBuilder m => PrimExp v -> m (Exp (Rep m)) Source #

ToExp v => ToExp (TPrimExp t v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp.Convert

Methods

toExp :: MonadBuilder m => TPrimExp t v -> m (Exp (Rep m)) Source #

toSubExp :: (MonadBuilder m, ToExp a) => String -> a -> m SubExp Source #

A convenient composition of letSubExp and toExp.