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 |
Turn CoreHW terms into normalized CoreHW Terms
- runNormalization :: CLaSHOpts -> Supply -> HashMap TmName (Type, SrcSpan, Term) -> (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) -> HashMap TyConName TyCon -> IntMap TyConName -> (HashMap TyConName TyCon -> Bool -> Term -> Term) -> PrimMap BlackBoxTemplate -> HashMap TmName Bool -> NormalizeSession a -> a
- normalize :: [TmName] -> NormalizeSession (HashMap TmName (Type, SrcSpan, Term))
- normalize' :: TmName -> NormalizeSession ([TmName], (TmName, (Type, SrcSpan, Term)))
- rewriteExpr :: (String, NormRewrite) -> (String, Term) -> NormalizeSession Term
- checkNonRecursive :: TmName -> HashMap TmName (Type, SrcSpan, Term) -> HashMap TmName (Type, SrcSpan, Term)
- cleanupGraph :: TmName -> HashMap TmName (Type, SrcSpan, Term) -> NormalizeSession (HashMap TmName (Type, SrcSpan, Term))
- data CallTree
- mkCallTree :: [TmName] -> HashMap TmName (Type, SrcSpan, Term) -> TmName -> CallTree
- stripArgs :: [TmName] -> [Id] -> [Either Term Type] -> Maybe [Either Term Type]
- flattenNode :: CallTree -> NormalizeSession (Either CallTree ((TmName, Term), [CallTree]))
- flattenCallTree :: CallTree -> NormalizeSession CallTree
- callTreeToList :: [TmName] -> CallTree -> ([TmName], [(TmName, (Type, SrcSpan, Term))])
Documentation
:: CLaSHOpts | Level of debug messages to print |
-> Supply | UniqueSupply |
-> HashMap TmName (Type, SrcSpan, Term) | Global Binders |
-> (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) | Hardcoded Type -> HWType translator |
-> HashMap TyConName TyCon | TyCon cache |
-> IntMap TyConName | Tuple TyCon cache |
-> (HashMap TyConName TyCon -> Bool -> Term -> Term) | Hardcoded evaluator (delta-reduction) |
-> PrimMap BlackBoxTemplate | Primitive Definitions |
-> HashMap TmName Bool | Map telling whether a components is part of a recursive group |
-> NormalizeSession a | NormalizeSession to run |
-> a |
Run a NormalizeSession in a given environment
normalize' :: TmName -> NormalizeSession ([TmName], (TmName, (Type, SrcSpan, Term))) Source
:: (String, NormRewrite) | Transformation to apply |
-> (String, Term) | Term to transform |
-> NormalizeSession Term |
Rewrite a term according to the provided transformation
:: TmName | topEntity |
-> HashMap TmName (Type, SrcSpan, Term) | List of normalized binders |
-> HashMap TmName (Type, SrcSpan, Term) |
Check if the call graph (second argument), starting at the topEnity
(first argument) is non-recursive. Returns the list of normalized terms if
call graph is indeed non-recursive, errors otherwise.
cleanupGraph :: TmName -> HashMap TmName (Type, SrcSpan, Term) -> NormalizeSession (HashMap TmName (Type, SrcSpan, Term)) Source
Perform general "clean up" of the normalized (non-recursive) function hierarchy. This includes:
- Inlining functions that simply "wrap" another function
flattenNode :: CallTree -> NormalizeSession (Either CallTree ((TmName, Term), [CallTree])) Source