Copyright | (C) 2012-2016 University of Twente 2016 Myrtle Software Ltd 2017 Google Inc. 2021-2023 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Clash.Rewrite.Util
Description
Utilities for rewriting: e.g. inlining, specialisation, etc.
Synopsis
- apply :: String -> Rewrite extra -> Rewrite extra
- isUntranslatableType :: Bool -> Type -> RewriteMonad extra Bool
- runRewriteSession :: RewriteEnv -> RewriteState extra -> RewriteMonad extra a -> IO a
- changed :: a -> RewriteMonad extra a
- isUntranslatable :: Bool -> Term -> RewriteMonad extra Bool
- mkDerivedName :: TransformContext -> OccName -> TmName
- mkTmBinderFor :: MonadUnique m => InScopeSet -> TyConMap -> Name a -> Term -> m Id
- isFromInt :: Text -> Bool
- whnfRW :: Bool -> TransformContext -> Term -> Rewrite extra -> RewriteMonad extra Term
- inlineBinders :: (Term -> LetBinding -> RewriteMonad extra Bool) -> Rewrite extra
- inlineOrLiftBinders :: (LetBinding -> RewriteMonad extra Bool) -> (Term -> LetBinding -> Bool) -> Rewrite extra
- isJoinPointIn :: Id -> Term -> Bool
- isVoidWrapper :: Term -> Bool
- zoomExtra :: State extra a -> RewriteMonad extra a
- removeUnusedBinders :: Bind Term -> Term -> Maybe Term
- setChanged :: RewriteMonad extra ()
- mkBinderFor :: MonadUnique m => InScopeSet -> TyConMap -> Name a -> Either Term Type -> m (Either Id TyVar)
- mkFunction :: TmName -> SrcSpan -> InlineSpec -> Term -> RewriteMonad extra Id
- normalizeTermTypes :: TyConMap -> Term -> Term
- normalizeId :: TyConMap -> Id -> Id
- runRewrite :: String -> InScopeSet -> Rewrite extra -> Term -> RewriteMonad extra Term
- applyDebug :: TransformContext -> String -> Term -> Bool -> Term -> RewriteMonad extra Term
- findAccidentialShadows :: Term -> [[Id]]
- closestLetBinder :: Context -> Maybe Id
- cloneNameWithInScopeSet :: MonadUnique m => InScopeSet -> Name a -> m (Name a)
- substituteBinders :: InScopeSet -> [LetBinding] -> [LetBinding] -> Term -> ([LetBinding], ([LetBinding], Term))
- tailCalls :: Id -> Term -> Maybe Int
- liftAndSubsituteBinders :: InScopeSet -> [LetBinding] -> [LetBinding] -> Term -> RewriteMonad extra ([LetBinding], Term)
- liftBinding :: LetBinding -> RewriteMonad extra LetBinding
- cloneNameWithBindingMap :: MonadUnique m => BindingMap -> Name a -> m (Name a)
- addGlobalBind :: TmName -> Type -> SrcSpan -> InlineSpec -> Term -> RewriteMonad extra ()
- bindPureHeap :: TyConMap -> PureHeap -> Rewrite extra -> Rewrite extra
- module Clash.Rewrite.WorkFree
Documentation
Arguments
:: String | Name of the transformation |
-> Rewrite extra | Transformation to be applied |
-> Rewrite extra |
Record if a transformation is successfully applied
Arguments
:: Bool | String representable |
-> Type | |
-> RewriteMonad extra Bool |
Determine if a type cannot be represented in hardware
runRewriteSession :: RewriteEnv -> RewriteState extra -> RewriteMonad extra a -> IO a Source #
Evaluate a RewriteSession to its inner monad.
changed :: a -> RewriteMonad extra a Source #
Identity function that additionally notifies that a transformation has changed the expression
Arguments
:: Bool | String representable |
-> Term | |
-> RewriteMonad extra Bool |
Determine if a term cannot be represented in hardware
mkDerivedName :: TransformContext -> OccName -> TmName Source #
Arguments
:: MonadUnique m | |
=> InScopeSet | |
-> TyConMap | TyCon cache |
-> Name a | Name of the new binder |
-> Term | Term to bind |
-> m Id |
Make a new binder and variable reference for a term
Arguments
:: Bool | Whether the expression we're reducing to WHNF is the subject of a case expression. |
-> TransformContext | |
-> Term | |
-> Rewrite extra | |
-> RewriteMonad extra Term |
Evaluate an expression to weak-head normal form (WHNF), and apply a transformation on the expression in WHNF.
Arguments
:: (Term -> LetBinding -> RewriteMonad extra Bool) | Property test |
-> Rewrite extra |
Inline the binders in a let-binding that have a certain property
Arguments
:: (LetBinding -> RewriteMonad extra Bool) | Property test |
-> (Term -> LetBinding -> Bool) | Test whether to lift or inline
|
-> Rewrite extra |
Determine whether a binder is a join-point created for a complex case expression.
A join-point is when a local function only occurs in tail-call positions, and when it does, more than once.
isVoidWrapper :: Term -> Bool Source #
Determines whether a function has the following shape:
\(w :: Void) -> f a b c
i.e. is a wrapper around a (partially) applied function f
, where the
introduced argument w
is not used by f
zoomExtra :: State extra a -> RewriteMonad extra a Source #
Lift an action working in the _extra
state to the RewriteMonad
removeUnusedBinders :: Bind Term -> Term -> Maybe Term Source #
Remove unused binders in given let-binding. Returns Nothing if no unused binders were found.
setChanged :: RewriteMonad extra () Source #
Notify that a transformation has changed the expression
Arguments
:: MonadUnique m | |
=> InScopeSet | |
-> TyConMap | TyCon cache |
-> Name a | Name of the new binder |
-> Either Term Type | Type or Term to bind |
-> m (Either Id TyVar) |
Make a new binder and variable reference for either a term or a type
Arguments
:: TmName | Name of the function |
-> SrcSpan | |
-> InlineSpec | |
-> Term | Term bound to the function |
-> RewriteMonad extra Id | Name with a proper unique and the type of the function |
Make a global function for a name-term tuple
Arguments
:: String | Name of the transformation |
-> InScopeSet | |
-> Rewrite extra | Transformation to perform |
-> Term | Term to transform |
-> RewriteMonad extra Term |
Perform a transformation on a Term
Arguments
:: TransformContext | |
-> String | Name of the transformation |
-> Term | Original expression |
-> Bool | Whether the rewrite indicated change |
-> Term | New expression |
-> RewriteMonad extra Term |
findAccidentialShadows :: Term -> [[Id]] Source #
Some transformations might erroneously introduce shadowing. For example, a transformation might result in:
let a = ... b = ... a = ...
where the last a
, shadows the first, while Clash assumes that this can't
happen. This function finds those constructs and a list of found duplicates.
cloneNameWithInScopeSet :: MonadUnique m => InScopeSet -> Name a -> m (Name a) Source #
Create a new name out of the given name, but with another unique. Resulting unique is guaranteed to not be in the given InScopeSet.
Arguments
:: InScopeSet | |
-> [LetBinding] | Let-binders to substitute |
-> [LetBinding] | Let-binders where substitution takes place |
-> Term | Body where substitution takes place |
-> ([LetBinding], ([LetBinding], Term)) |
|
Inline the first set of binder into the second set of binders and into the body of the original let expression.
Count the number of (only) tail calls of a function in an expression.
Nothing
indicates that the function was used in a non-tail call position.
liftAndSubsituteBinders Source #
Arguments
:: InScopeSet | |
-> [LetBinding] | Let-binders to lift, and substitute the lifted result |
-> [LetBinding] | Lef-binders where substitution takes place |
-> Term | Body where substitution takes place |
-> RewriteMonad extra ([LetBinding], Term) |
Lift the first set of binders to the level of global bindings, and substitute these lifted bindings into the second set of binders and the body of the original let expression.
liftBinding :: LetBinding -> RewriteMonad extra LetBinding Source #
Create a global function for a Let-binding and return a Let-binding where the RHS is a reference to the new global function applied to the free variables of the original RHS
cloneNameWithBindingMap :: MonadUnique m => BindingMap -> Name a -> m (Name a) Source #
Create a new name out of the given name, but with another unique. Resulting unique is guaranteed to not be in the given BindingMap.
addGlobalBind :: TmName -> Type -> SrcSpan -> InlineSpec -> Term -> RewriteMonad extra () Source #
Add a function to the set of global binders
bindPureHeap :: TyConMap -> PureHeap -> Rewrite extra -> Rewrite extra Source #
Binds variables on the PureHeap over the result of the rewrite
To prevent unnecessary rewrites only do this when rewrite changed something.
module Clash.Rewrite.WorkFree