Copyright | (C) 2012-2016 University of Twente |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Utility functions used by the normalisation transformations
Synopsis
- data ConstantSpecInfo = ConstantSpecInfo {
- csrNewBindings :: [(Id, Term)]
- csrNewTerm :: !Term
- csrFoundConstant :: !Bool
- isConstantArg :: Text -> Int -> RewriteMonad NormalizeState Bool
- shouldReduce :: Context -> RewriteMonad NormalizeState Bool
- alreadyInlined :: Id -> Id -> NormalizeMonad (Maybe Int)
- addNewInline :: Id -> Id -> NormalizeMonad ()
- specializeNorm :: NormRewrite
- isRecursiveBndr :: Id -> NormalizeSession Bool
- isClosed :: TyConMap -> Term -> Bool
- callGraph :: BindingMap -> Id -> CallGraph
- collectCallGraphUniques :: CallGraph -> HashSet Unique
- classifyFunction :: Term -> TermClassification
- isCheapFunction :: Term -> Bool
- isNonRecursiveGlobalVar :: Term -> NormalizeSession Bool
- constantSpecInfo :: TransformContext -> Term -> RewriteMonad NormalizeState ConstantSpecInfo
- normalizeTopLvlBndr :: Bool -> Id -> Binding -> NormalizeSession Binding
- rewriteExpr :: (String, NormRewrite) -> (String, Term) -> (Id, SrcSpan) -> NormalizeSession Term
- removedTm :: Type -> Term
- mkInlineTick :: Id -> TickInfo
- substWithTyEq :: Term -> Term
- tvSubstWithTyEq :: Type -> Type
Documentation
data ConstantSpecInfo Source #
ConstantSpecInfo | |
|
Instances
Show ConstantSpecInfo Source # | |
Defined in Clash.Normalize.Util showsPrec :: Int -> ConstantSpecInfo -> ShowS # show :: ConstantSpecInfo -> String # showList :: [ConstantSpecInfo] -> ShowS # |
:: Text | Primitive name |
-> Int | Argument number |
-> RewriteMonad NormalizeState Bool | Yields |
Determine if argument should reduce to a constant given a primitive and an argument number. Caches results.
:: Context | ..in the current transformcontext |
-> RewriteMonad NormalizeState Bool |
Given a list of transformation contexts, determine if any of the contexts indicates that the current arg is to be reduced to a constant / literal.
:: Id | Function we want to inline |
-> Id | Function in which we want to perform the inlining |
-> NormalizeMonad (Maybe Int) |
Determine if a function is already inlined in the context of the NetlistMonad
:: Id | Function we want to inline |
-> Id | Function in which we want to perform the inlining |
-> NormalizeMonad () |
specializeNorm :: NormRewrite Source #
Specialize under the Normalization Monad
isRecursiveBndr :: Id -> NormalizeSession Bool Source #
Assert whether a name is a reference to a recursive binder.
callGraph :: BindingMap -> Id -> CallGraph Source #
Create a call graph for a set of global binders, given a root
collectCallGraphUniques :: CallGraph -> HashSet Unique Source #
Collect all binders mentioned in CallGraph into a HashSet
classifyFunction :: Term -> TermClassification Source #
Give a "performance/size" classification of a function in normal form.
isCheapFunction :: Term -> Bool Source #
Determine whether a function adds a lot of hardware or not.
It is considered expensive when it has 2 or more of the following components:
- functions
- primitives
- selections (multiplexers)
isNonRecursiveGlobalVar :: Term -> NormalizeSession Bool Source #
Test whether a given term represents a non-recursive global variable
constantSpecInfo :: TransformContext -> Term -> RewriteMonad NormalizeState ConstantSpecInfo Source #
Calculate constant spec info. The goal of this function is to analyze a given term and yield a new term that:
- Leaves all the constant parts as they were.
- Has all _variable_ parts replaced by a newly generated identifier.
The result structure will additionally contain:
- Whether the function found any constant parts at all
- A list of let-bindings binding the aforementioned identifiers with the term they replaced.
This can be used in functions wanting to constant specialize over partially constant data structures.
normalizeTopLvlBndr :: Bool -> Id -> Binding -> NormalizeSession Binding Source #
:: (String, NormRewrite) | Transformation to apply |
-> (String, Term) | Term to transform |
-> (Id, SrcSpan) | Renew current function being rewritten |
-> NormalizeSession Term |
Rewrite a term according to the provided transformation
mkInlineTick :: Id -> TickInfo Source #
A tick to prefix an inlined expression with it's original name. For example, given
foo = bar -- ... bar = baz -- ... baz = quuz -- ...
if bar is inlined into foo, then the name of the component should contain the name of the inlined component. This tick ensures that the component in foo is called bar_baz instead of just baz.
substWithTyEq :: Term -> Term Source #
Turn type equality constraints into substitutions and apply them.
So given:
/\dom . \(eq : dom ~ "System") . \(eta : Signal dom Bool) . eta
we create the substitution [dom := System] and apply it to create:
\(eq : "System" ~ "System") . \(eta : Signal "System" Bool) . eta
NB: Users of this function should ensure it's only applied to TopEntities
tvSubstWithTyEq :: Type -> Type Source #
The type equivalent of substWithTyEq