Safe Haskell | None |
---|---|
Language | Haskell2010 |
The code generator cannot handle the array combinators (map
and
friends), so this module was written to transform them into the
equivalent do-loops. The transformation is currently rather naive,
and - it's certainly worth considering when we can express such
transformations in-place.
Synopsis
- transformFunDef :: (MonadFreshNames m, Bindable tolore, BinderOps tolore, LetAttr SOACS ~ LetAttr tolore, CanBeAliased (Op tolore)) => FunDef -> m (FunDef tolore)
- type Transformer m = (MonadBinder m, Bindable (Lore m), BinderOps (Lore m), LocalScope (Lore m) m, LetAttr SOACS ~ LetAttr (Lore m), LParamAttr SOACS ~ LParamAttr (Lore m), CanBeAliased (Op (Lore m)))
- transformStmRecursively :: Transformer m => Stm -> m ()
- transformLambda :: (MonadFreshNames m, Bindable lore, BinderOps lore, LocalScope somelore m, SameScope somelore lore, LetAttr SOACS ~ LetAttr lore, CanBeAliased (Op lore)) => Lambda -> m (Lambda lore)
- transformSOAC :: Transformer m => Pattern (Lore m) -> SOAC (Lore m) -> m ()
- transformBody :: Transformer m => Body -> m (Body (Lore m))
- doLoopMapAccumL :: (LocalScope (Lore m) m, MonadBinder m, Bindable (Lore m), BinderOps (Lore m), LetAttr (Lore m) ~ Type, CanBeAliased (Op (Lore m))) => SubExp -> Lambda (Aliases (Lore m)) -> [SubExp] -> [VName] -> [VName] -> m (Exp (Lore m))
- doLoopMapAccumL' :: (LocalScope (Lore m) m, MonadBinder m, Bindable (Lore m), BinderOps (Lore m), LetAttr (Lore m) ~ Type, CanBeAliased (Op (Lore m))) => SubExp -> Lambda (Aliases (Lore m)) -> [SubExp] -> [VName] -> [VName] -> m ([(FParam (Lore m), SubExp)], VName, Body (Lore m))
Documentation
transformFunDef :: (MonadFreshNames m, Bindable tolore, BinderOps tolore, LetAttr SOACS ~ LetAttr tolore, CanBeAliased (Op tolore)) => FunDef -> m (FunDef tolore) Source #
type Transformer m = (MonadBinder m, Bindable (Lore m), BinderOps (Lore m), LocalScope (Lore m) m, LetAttr SOACS ~ LetAttr (Lore m), LParamAttr SOACS ~ LParamAttr (Lore m), CanBeAliased (Op (Lore m))) Source #
The constraints that a monad must uphold in order to be used for first-order transformation.
transformStmRecursively :: Transformer m => Stm -> m () Source #
First transform any nested Body
or Lambda
elements, then
apply transformSOAC
if the expression is a SOAC.
transformLambda :: (MonadFreshNames m, Bindable lore, BinderOps lore, LocalScope somelore m, SameScope somelore lore, LetAttr SOACS ~ LetAttr lore, CanBeAliased (Op lore)) => Lambda -> m (Lambda lore) Source #
Recursively first-order-transform a lambda.
transformSOAC :: Transformer m => Pattern (Lore m) -> SOAC (Lore m) -> m () Source #
transformBody :: Transformer m => Body -> m (Body (Lore m)) Source #
Utility
doLoopMapAccumL :: (LocalScope (Lore m) m, MonadBinder m, Bindable (Lore m), BinderOps (Lore m), LetAttr (Lore m) ~ Type, CanBeAliased (Op (Lore m))) => SubExp -> Lambda (Aliases (Lore m)) -> [SubExp] -> [VName] -> [VName] -> m (Exp (Lore m)) Source #
Turn a Haskell-style mapAccumL into a sequential do-loop. This
is the guts of transforming a Redomap
.