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

Futhark.Optimise.Simplify.Rule

Description

This module defines the concept of a simplification rule for bindings. The intent is that you pass some context (such as symbol table) and a binding, and is given back a sequence of bindings that compute the same result, but are "better" in some sense.

These rewrite rules are "local", in that they do not maintain any state or look at the program as a whole. Compare this to the fusion algorithm in Futhark.Optimise.Fusion.Fusion, which must be implemented as its own pass.

Synopsis

The rule monad

data RuleM lore a Source #

The monad in which simplification rules are evaluated.

Instances

Instances details
ASTLore lore => LocalScope lore (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

localScope :: Scope lore -> RuleM lore a -> RuleM lore a Source #

ASTLore lore => HasScope lore (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

lookupType :: VName -> RuleM lore Type Source #

lookupInfo :: VName -> RuleM lore (NameInfo lore) Source #

askScope :: RuleM lore (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RuleM lore a Source #

Monad (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

(>>=) :: RuleM lore a -> (a -> RuleM lore b) -> RuleM lore b #

(>>) :: RuleM lore a -> RuleM lore b -> RuleM lore b #

return :: a -> RuleM lore a #

Functor (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

fmap :: (a -> b) -> RuleM lore a -> RuleM lore b #

(<$) :: a -> RuleM lore b -> RuleM lore a #

Applicative (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

pure :: a -> RuleM lore a #

(<*>) :: RuleM lore (a -> b) -> RuleM lore a -> RuleM lore b #

liftA2 :: (a -> b -> c) -> RuleM lore a -> RuleM lore b -> RuleM lore c #

(*>) :: RuleM lore a -> RuleM lore b -> RuleM lore b #

(<*) :: RuleM lore a -> RuleM lore b -> RuleM lore a #

MonadFreshNames (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

(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 #

type Lore (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

type Lore (RuleM lore) = lore

liftMaybe :: Maybe a -> RuleM lore a Source #

Rule definition

data Rule lore Source #

An efficient way of encoding whether a simplification rule should even be attempted.

Constructors

Simplify (RuleM lore ())

Give it a shot.

Skip

Don't bother.

data SimplificationRule lore a Source #

A simplification rule takes some argument and a statement, and tries to simplify the statement.

Constructors

RuleGeneric (RuleGeneric lore a) 
RuleBasicOp (RuleBasicOp lore a) 
RuleIf (RuleIf lore a) 
RuleDoLoop (RuleDoLoop lore a) 
RuleOp (RuleOp lore a) 

type RuleGeneric lore a = a -> Stm lore -> Rule lore Source #

type RuleBasicOp lore a = a -> Pattern lore -> StmAux (ExpDec lore) -> BasicOp -> Rule lore Source #

type RuleIf lore a = a -> Pattern lore -> StmAux (ExpDec lore) -> (SubExp, BodyT lore, BodyT lore, IfDec (BranchType lore)) -> Rule lore Source #

type RuleDoLoop lore a = a -> Pattern lore -> StmAux (ExpDec lore) -> ([(FParam lore, SubExp)], [(FParam lore, SubExp)], LoopForm lore, BodyT lore) -> Rule lore Source #

Top-down rules

type TopDown lore = SymbolTable lore Source #

Context for a rule applied during top-down traversal of the program. Takes a symbol table as argument.

type TopDownRuleIf lore = RuleIf lore (TopDown lore) Source #

type TopDownRuleDoLoop lore = RuleDoLoop lore (TopDown lore) Source #

type TopDownRuleOp lore = RuleOp lore (TopDown lore) Source #

Bottom-up rules

type BottomUp lore = (SymbolTable lore, UsageTable) Source #

Context for a rule applied during bottom-up traversal of the program. Takes a symbol table and usage table as arguments.

type BottomUpRuleIf lore = RuleIf lore (BottomUp lore) Source #

type BottomUpRuleOp lore = RuleOp lore (BottomUp lore) Source #

Assembling rules

data RuleBook lore Source #

A collection of both top-down and bottom-up rules.

Instances

Instances details
Semigroup (RuleBook lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

(<>) :: RuleBook lore -> RuleBook lore -> RuleBook lore #

sconcat :: NonEmpty (RuleBook lore) -> RuleBook lore #

stimes :: Integral b => b -> RuleBook lore -> RuleBook lore #

Monoid (RuleBook lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

mempty :: RuleBook lore #

mappend :: RuleBook lore -> RuleBook lore -> RuleBook lore #

mconcat :: [RuleBook lore] -> RuleBook lore #

ruleBook :: [TopDownRule m] -> [BottomUpRule m] -> RuleBook m Source #

Construct a rule book from a collection of rules.

Applying rules

topDownSimplifyStm :: (MonadFreshNames m, HasScope lore m) => RuleBook lore -> SymbolTable lore -> Stm lore -> m (Maybe (Stms lore)) Source #

simplifyStm lookup bnd performs simplification of the binding bnd. If simplification is possible, a replacement list of bindings is returned, that bind at least the same names as the original binding (and possibly more, for intermediate results).

bottomUpSimplifyStm :: (MonadFreshNames m, HasScope lore m) => RuleBook lore -> (SymbolTable lore, UsageTable) -> Stm lore -> m (Maybe (Stms lore)) Source #

simplifyStm uses bnd performs simplification of the binding bnd. If simplification is possible, a replacement list of bindings is returned, that bind at least the same names as the original binding (and possibly more, for intermediate results). The first argument is the set of names used after this binding.