futhark-0.7.4: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.Construct

Contents

Synopsis

Documentation

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

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 #

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

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

eAbs :: MonadBinder m => 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 #

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

Note: unsigned division.

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.

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

Construct an Index expressions that splits an array in different parts along the outer dimension.

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

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.

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 BasicOps. You should call this function within some monad that allows you to collect the actions performed (say, Writer).

Convenience

simpleMkLetNames :: (ExpAttr lore ~ (), LetAttr 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
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 #