Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines a convenience typeclass for creating normalised programs.
Synopsis
- class (Attributes lore, FParamAttr lore ~ DeclType, LParamAttr lore ~ Type, RetType lore ~ DeclExtType, BranchType lore ~ ExtType, SetType (LetAttr lore)) => Bindable lore where
- mkLet :: Bindable lore => [Ident] -> [Ident] -> Exp lore -> Stm lore
- class (Attributes (Lore m), MonadFreshNames m, Applicative m, Monad m, LocalScope (Lore m) m) => MonadBinder m where
- type Lore m :: Type
- mkExpAttrM :: Pattern (Lore m) -> Exp (Lore m) -> m (ExpAttr (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
- mkLetM :: MonadBinder m => Pattern (Lore m) -> Exp (Lore m) -> m (Stm (Lore m))
- bodyStms :: BodyT lore -> Stms lore
- 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 [Ident]
- letBind_ :: MonadBinder m => Pattern (Lore m) -> Exp (Lore m) -> m ()
- letBindNames :: MonadBinder m => [VName] -> Exp (Lore m) -> m [Ident]
- 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]
- module Futhark.MonadFreshNames
Documentation
class (Attributes lore, FParamAttr lore ~ DeclType, LParamAttr lore ~ Type, RetType lore ~ DeclExtType, BranchType lore ~ ExtType, SetType (LetAttr 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 #
mkExpAttr :: Pattern lore -> Exp lore -> ExpAttr lore Source #
mkBody :: Stms lore -> Result -> Body lore Source #
mkLetNames :: (MonadFreshNames m, HasScope lore m) => [VName] -> Exp lore -> m (Stm lore) Source #
Instances
class (Attributes (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.
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.
mkExpAttrM :: Pattern (Lore m) -> Exp (Lore m) -> m (ExpAttr (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 #
addStms :: Stms (Lore m) -> m () Source #
collectStms :: m a -> m (a, Stms (Lore m)) Source #
certifying :: Certificates -> m a -> m a Source #
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
.
letBindNames :: MonadBinder m => [VName] -> Exp (Lore m) -> m [Ident] Source #
letBindNames_ :: MonadBinder m => [VName] -> Exp (Lore m) -> m () Source #
collectStms_ :: MonadBinder m => m a -> m (Stms (Lore m)) Source #
module Futhark.MonadFreshNames