Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module defines a convenience typeclass for creating normalised programs.
See Futhark.Construct for a high-level description.
Synopsis
- class (ASTLore lore, FParamInfo lore ~ DeclType, LParamInfo lore ~ Type, RetType lore ~ DeclExtType, BranchType lore ~ ExtType, SetType (LetDec lore)) => Bindable lore where
- mkLet :: Bindable lore => [Ident] -> [Ident] -> Exp lore -> Stm lore
- mkLet' :: Bindable lore => [Ident] -> [Ident] -> StmAux a -> Exp lore -> Stm lore
- class (ASTLore (Lore m), MonadFreshNames m, Applicative m, Monad m, LocalScope (Lore m) m) => MonadBinder m where
- type Lore m :: Type
- mkExpDecM :: Pattern (Lore m) -> Exp (Lore m) -> m (ExpDec (Lore m))
- mkBodyM :: Stms (Lore m) -> Result -> m (Body (Lore m))
- mkLetNamesM :: [VName] -> Exp (Lore m) -> m (Stm (Lore m))
- addStm :: Stm (Lore m) -> m ()
- addStms :: Stms (Lore m) -> m ()
- collectStms :: m a -> m (a, Stms (Lore m))
- certifying :: Certificates -> m a -> m a
- insertStms :: Bindable lore => Stms lore -> Body lore -> Body lore
- insertStm :: Bindable lore => Stm lore -> Body lore -> Body lore
- letBind :: MonadBinder m => Pattern (Lore m) -> Exp (Lore m) -> m ()
- letBindNames :: MonadBinder m => [VName] -> Exp (Lore m) -> m ()
- collectStms_ :: MonadBinder m => m a -> m (Stms (Lore m))
- bodyBind :: MonadBinder m => Body (Lore m) -> m [SubExp]
- attributing :: MonadBinder m => Attrs -> m a -> m a
- auxing :: MonadBinder m => StmAux anylore -> m a -> m a
- module Futhark.MonadFreshNames
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.
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
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.
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
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.
module Futhark.MonadFreshNames