futhark-0.18.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe
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 MonadBinder 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.

MonadBinder

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

The BinderT monad (and its convenient Binder version) provides the simplest implementation of MonadBinder.

Higher-level building blocks

On top of the raw facilities provided by MonadBinder, 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)

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

Documentation

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

eIf' :: (MonadBinder m, BranchType (Lore m) ~ ExtType) => m (Exp (Lore m)) -> m (Body (Lore m)) -> m (Body (Lore m)) -> IfSort -> m (Exp (Lore m)) Source #

As eIf, but an IfSort can be given.

eBinOp :: MonadBinder m => BinOp -> m (Exp (Lore m)) -> m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

eCmpOp :: MonadBinder m => CmpOp -> m (Exp (Lore m)) -> m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

eConvOp :: MonadBinder m => ConvOp -> m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

eSignum :: MonadBinder m => m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

eCopy :: MonadBinder m => m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

eAssert :: MonadBinder m => m (Exp (Lore m)) -> ErrorMsg SubExp -> SrcLoc -> m (Exp (Lore m)) Source #

eBody :: MonadBinder m => [m (Exp (Lore m))] -> m (Body (Lore m)) Source #

eLambda :: MonadBinder m => Lambda (Lore m) -> [m (Exp (Lore m))] -> m [SubExp] Source #

eRoundToMultipleOf :: MonadBinder m => IntType -> m (Exp (Lore m)) -> m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

eSliceArray :: MonadBinder m => Int -> VName -> m (Exp (Lore m)) -> m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

Construct an Index expressions that slices an array with unit stride.

eBlank :: MonadBinder m => Type -> m (Exp (Lore m)) Source #

Construct an unspecified value of the given type.

eAll :: MonadBinder m => [SubExp] -> m (Exp (Lore m)) Source #

True if all operands are true.

eOutOfBounds :: MonadBinder m => VName -> [m (Exp (Lore m))] -> m (Exp (Lore m)) Source #

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

eWriteArray :: (MonadBinder m, BranchType (Lore m) ~ ExtType) => VName -> [m (Exp (Lore m))] -> m (Exp (Lore m)) -> m (Exp (Lore m)) Source #

Write to an index of the array, if within bounds. Otherwise, nothing. Produces the updated array.

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

Zero-extend to the given integer type.

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

Sign-extend to the given integer type.

resultBody :: Bindable lore => [SubExp] -> Body lore Source #

Conveniently construct a body that contains no bindings.

resultBodyM :: MonadBinder m => [SubExp] -> m (Body (Lore m)) Source #

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

insertStmsM :: MonadBinder m => m (Body (Lore m)) -> m (Body (Lore m)) Source #

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

mapResult :: Bindable lore => (Result -> Body lore) -> Body lore -> Body lore Source #

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

foldBinOp :: MonadBinder m => BinOp -> SubExp -> [SubExp] -> m (Exp (Lore m)) Source #

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

binOpLambda :: (MonadBinder m, Bindable (Lore m)) => BinOp -> PrimType -> m (Lambda (Lore 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 :: (MonadBinder m, Bindable (Lore m)) => CmpOp -> m (Lambda (Lore m)) Source #

As binOpLambda, but for CmpOps.

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

Convenience

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

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

class ToExp a where Source #

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

Methods

toExp :: MonadBinder m => a -> m (Exp (Lore m)) Source #

Instances

Instances details
ToExp VName Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBinder m => VName -> m (Exp (Lore m)) Source #

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBinder m => SubExp -> m (Exp (Lore m)) Source #

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

Defined in Futhark.Analysis.PrimExp.Convert

Methods

toExp :: MonadBinder m => PrimExp v -> m (Exp (Lore m)) Source #

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

Defined in Futhark.Analysis.PrimExp.Convert

Methods

toExp :: MonadBinder m => TPrimExp t v -> m (Exp (Lore m)) Source #

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

A convenient composition of letSubExp and toExp.