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

Futhark.Binder.Class

Description

This module defines a convenience typeclass for creating normalised programs.

See Futhark.Construct for a high-level description.

Synopsis

Documentation

class (ASTLore lore, FParamInfo lore ~ DeclType, LParamInfo lore ~ Type, RetType lore ~ DeclExtType, BranchType lore ~ ExtType, SetType (LetDec lore)) => Bindable lore where Source #

The class of lores that can be constructed solely from an expression, within some monad. Very important: the methods should not have any significant side effects! They may be called more often than you think, and the results thrown away. If used exclusively within a MonadBinder instance, it is acceptable for them to create new bindings, however.

Methods

mkExpPat :: [Ident] -> [Ident] -> Exp lore -> Pattern lore Source #

mkExpDec :: Pattern lore -> Exp lore -> ExpDec lore Source #

mkBody :: Stms lore -> Result -> Body lore Source #

mkLetNames :: (MonadFreshNames m, HasScope lore m) => [VName] -> Exp lore -> m (Stm lore) Source #

Instances

Instances details
Bindable Seq Source # 
Instance details

Defined in Futhark.IR.Seq

Bindable SOACS Source # 
Instance details

Defined in Futhark.IR.SOACS

Bindable MC Source # 
Instance details

Defined in Futhark.IR.MC

Bindable Kernels Source # 
Instance details

Defined in Futhark.IR.Kernels

(Bindable lore, CanBeAliased (Op lore)) => Bindable (Aliases lore) Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

mkExpPat :: [Ident] -> [Ident] -> Exp (Aliases lore) -> Pattern (Aliases lore) Source #

mkExpDec :: Pattern (Aliases lore) -> Exp (Aliases lore) -> ExpDec (Aliases lore) Source #

mkBody :: Stms (Aliases lore) -> Result -> Body (Aliases lore) Source #

mkLetNames :: (MonadFreshNames m, HasScope (Aliases lore) m) => [VName] -> Exp (Aliases lore) -> m (Stm (Aliases lore)) Source #

(Bindable lore, CanBeWise (Op lore)) => Bindable (Wise lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

mkExpPat :: [Ident] -> [Ident] -> Exp (Wise lore) -> Pattern (Wise lore) Source #

mkExpDec :: Pattern (Wise lore) -> Exp (Wise lore) -> ExpDec (Wise lore) Source #

mkBody :: Stms (Wise lore) -> Result -> Body (Wise lore) Source #

mkLetNames :: (MonadFreshNames m, HasScope (Wise lore) m) => [VName] -> Exp (Wise lore) -> m (Stm (Wise lore)) Source #

mkLet :: Bindable lore => [Ident] -> [Ident] -> Exp lore -> Stm lore Source #

Construct a Stm from identifiers for the context- and value part of the pattern, as well as the expression.

mkLet' :: Bindable lore => [Ident] -> [Ident] -> StmAux a -> Exp lore -> Stm lore Source #

Like mkLet, but also take attributes and certificates from the given StmAux.

class (ASTLore (Lore m), MonadFreshNames m, Applicative m, Monad m, LocalScope (Lore m) m) => MonadBinder m where Source #

A monad that supports the creation of bindings from expressions and bodies from bindings, with a specific lore. This is the main typeclass that a monad must implement in order for it to be useful for generating or modifying Futhark code. Most importantly maintains a current state of Stms (as well as a Scope) that have been added with addStm.

Very important: the methods should not have any significant side effects! They may be called more often than you think, and the results thrown away. It is acceptable for them to create new bindings, however.

Minimal complete definition

mkExpDecM, mkBodyM, mkLetNamesM, addStms, collectStms

Associated Types

type Lore m :: Type Source #

Methods

mkExpDecM :: Pattern (Lore m) -> Exp (Lore m) -> m (ExpDec (Lore m)) Source #

mkBodyM :: Stms (Lore m) -> Result -> m (Body (Lore m)) Source #

mkLetNamesM :: [VName] -> Exp (Lore m) -> m (Stm (Lore m)) Source #

addStm :: Stm (Lore m) -> m () Source #

Add a statement to the Stms under construction.

addStms :: Stms (Lore m) -> m () Source #

Add multiple statements to the Stms under construction.

collectStms :: m a -> m (a, Stms (Lore m)) Source #

Obtain the statements constructed during a monadic action, instead of adding them to the state.

certifying :: Certificates -> m a -> m a Source #

Add the provided certificates to any statements added during execution of the action.

Instances

Instances details
MonadBinder InternaliseM Source # 
Instance details

Defined in Futhark.Internalise.Monad

Associated Types

type Lore InternaliseM Source #

(ASTLore lore, BinderOps lore) => MonadBinder (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Associated Types

type Lore (RuleM lore) Source #

Methods

mkExpDecM :: Pattern (Lore (RuleM lore)) -> Exp (Lore (RuleM lore)) -> RuleM lore (ExpDec (Lore (RuleM lore))) Source #

mkBodyM :: Stms (Lore (RuleM lore)) -> Result -> RuleM lore (Body (Lore (RuleM lore))) Source #

mkLetNamesM :: [VName] -> Exp (Lore (RuleM lore)) -> RuleM lore (Stm (Lore (RuleM lore))) Source #

addStm :: Stm (Lore (RuleM lore)) -> RuleM lore () Source #

addStms :: Stms (Lore (RuleM lore)) -> RuleM lore () Source #

collectStms :: RuleM lore a -> RuleM lore (a, Stms (Lore (RuleM lore))) Source #

certifying :: Certificates -> RuleM lore a -> RuleM lore a Source #

(ASTLore lore, MonadFreshNames m, BinderOps lore) => MonadBinder (BinderT lore m) Source # 
Instance details

Defined in Futhark.Binder

Associated Types

type Lore (BinderT lore m) Source #

Methods

mkExpDecM :: Pattern (Lore (BinderT lore m)) -> Exp (Lore (BinderT lore m)) -> BinderT lore m (ExpDec (Lore (BinderT lore m))) Source #

mkBodyM :: Stms (Lore (BinderT lore m)) -> Result -> BinderT lore m (Body (Lore (BinderT lore m))) Source #

mkLetNamesM :: [VName] -> Exp (Lore (BinderT lore m)) -> BinderT lore m (Stm (Lore (BinderT lore m))) Source #

addStm :: Stm (Lore (BinderT lore m)) -> BinderT lore m () Source #

addStms :: Stms (Lore (BinderT lore m)) -> BinderT lore m () Source #

collectStms :: BinderT lore m a -> BinderT lore m (a, Stms (Lore (BinderT lore m))) Source #

certifying :: Certificates -> BinderT lore m a -> BinderT lore m a Source #

(Allocable fromlore tolore, Allocator tolore (AllocM fromlore tolore)) => MonadBinder (AllocM fromlore tolore) Source # 
Instance details

Defined in Futhark.Pass.ExplicitAllocations

Associated Types

type Lore (AllocM fromlore tolore) Source #

Methods

mkExpDecM :: Pattern (Lore (AllocM fromlore tolore)) -> Exp (Lore (AllocM fromlore tolore)) -> AllocM fromlore tolore (ExpDec (Lore (AllocM fromlore tolore))) Source #

mkBodyM :: Stms (Lore (AllocM fromlore tolore)) -> Result -> AllocM fromlore tolore (Body (Lore (AllocM fromlore tolore))) Source #

mkLetNamesM :: [VName] -> Exp (Lore (AllocM fromlore tolore)) -> AllocM fromlore tolore (Stm (Lore (AllocM fromlore tolore))) Source #

addStm :: Stm (Lore (AllocM fromlore tolore)) -> AllocM fromlore tolore () Source #

addStms :: Stms (Lore (AllocM fromlore tolore)) -> AllocM fromlore tolore () Source #

collectStms :: AllocM fromlore tolore a -> AllocM fromlore tolore (a, Stms (Lore (AllocM fromlore tolore))) Source #

certifying :: Certificates -> AllocM fromlore tolore a -> AllocM fromlore tolore a Source #

insertStms :: Bindable lore => Stms lore -> Body lore -> Body lore Source #

Add several bindings at the outermost level of a Body.

insertStm :: Bindable lore => Stm lore -> Body lore -> Body lore Source #

Add a single binding at the outermost level of a Body.

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

Add a statement with the given pattern and expression.

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

Add a statement with the given pattern element names and expression.

collectStms_ :: MonadBinder m => m a -> m (Stms (Lore m)) Source #

As collectStms, but throw away the ordinary result.

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

Add the statements of the body, then return the body result.

attributing :: MonadBinder m => Attrs -> m a -> m a Source #

Add the given attributes to any statements added by this action.

auxing :: MonadBinder m => StmAux anylore -> m a -> m a Source #

Add the certificates and attributes to any statements added by this action.