Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utility functions used by the normalisation transformations
- alreadyInlined :: TmName -> NormalizeMonad (Maybe Int)
- addNewInline :: TmName -> NormalizeMonad ()
- specializeNorm :: Bool -> NormRewrite
- isClosed :: (Functor m, Fresh m) => HashMap TyConName TyCon -> Term -> m Bool
- isConstant :: Term -> Bool
- callGraph :: [TmName] -> HashMap TmName (Type, Term) -> TmName -> [(TmName, [TmName])]
- recursiveComponents :: [(TmName, [TmName])] -> [[TmName]]
- lambdaDropPrep :: HashMap TmName (Type, Term) -> TmName -> HashMap TmName (Type, Term)
- lambdaDrop :: HashMap TmName (Type, Term) -> HashMap TmName [TmName] -> [TmName] -> (TmName, (Type, Term))
- dominator :: HashMap TmName [TmName] -> [TmName] -> Gr TmName TmName
- blockSink :: HashMap TmName (Type, Term) -> Gr TmName TmName -> LNode TmName -> (TmName, (Type, Term))
Documentation
alreadyInlined :: TmName -> NormalizeMonad (Maybe Int) Source
Determine if a function is already inlined in the context of the NetlistMonad
addNewInline :: TmName -> NormalizeMonad () Source
specializeNorm :: Bool -> NormRewrite Source
Specialize under the Normalization Monad
isClosed :: (Functor m, Fresh m) => HashMap TyConName TyCon -> Term -> m Bool Source
Determine if a term is closed
isConstant :: Term -> Bool Source
Determine if a term represents a constant
:: [TmName] | List of functions that should not be inspected |
-> HashMap TmName (Type, Term) | Global binders |
-> TmName | Root of the call graph |
-> [(TmName, [TmName])] |
Create a call graph for a set of global binders, given a root
Determine the sets of recursive components given the edges of a callgraph