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

Safe HaskellNone
LanguageHaskell2010

Futhark.Binder.Class

Description

This module defines a convenience typeclass for creating normalised programs.

Synopsis

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.

Methods

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
Bindable SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Bindable InKernel Source # 
Instance details

Defined in Futhark.Representation.Kernels

Bindable Kernels Source # 
Instance details

Defined in Futhark.Representation.Kernels

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

Defined in Futhark.Representation.Aliases

Methods

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

mkExpAttr :: Pattern (Aliases lore) -> Exp (Aliases lore) -> ExpAttr (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 #

mkExpAttr :: Pattern (Wise lore) -> Exp (Wise lore) -> ExpAttr (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 #

class (Attributes (Lore m), MonadFreshNames m, Applicative m, Monad m, LocalScope (Lore m) m, MonadFail 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.

Associated Types

type Lore m :: * Source #

Methods

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
MonadBinder InternaliseM Source # 
Instance details

Defined in Futhark.Internalise.Monad

Associated Types

type Lore InternaliseM :: Type Source #

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

Defined in Futhark.Optimise.Simplify.Rule

Associated Types

type Lore (RuleM lore) :: Type Source #

Methods

mkExpAttrM :: Pattern (Lore (RuleM lore)) -> Exp (Lore (RuleM lore)) -> RuleM lore (ExpAttr (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 #

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

Defined in Futhark.Binder

Associated Types

type Lore (BinderT lore m) :: Type Source #

Methods

mkExpAttrM :: Pattern (Lore (BinderT lore m)) -> Exp (Lore (BinderT lore m)) -> BinderT lore m (ExpAttr (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 #

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

bodyStms :: BodyT lore -> Stms lore Source #

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

Add several bindings at the outermost level of a BodyT.

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

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

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

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

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

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