Copyright | (C) 2012-2016 University of Twente 2016 Myrtle Software Ltd 2017 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Type and instance definitions for Rewrite modules
Synopsis
- data CoreContext
- data RewriteState extra = RewriteState {
- _transformCounter :: !Int
- _bindings :: !BindingMap
- _uniqSupply :: !Supply
- _curFun :: (TmName, SrcSpan)
- _nameCounter :: !Int
- _extra :: !extra
- uniqSupply :: forall extra. Lens' (RewriteState extra) Supply
- transformCounter :: forall extra. Lens' (RewriteState extra) Int
- nameCounter :: forall extra. Lens' (RewriteState extra) Int
- extra :: forall extra extra. Lens (RewriteState extra) (RewriteState extra) extra extra
- curFun :: forall extra. Lens' (RewriteState extra) (TmName, SrcSpan)
- bindings :: forall extra. Lens' (RewriteState extra) BindingMap
- data RewriteEnv = RewriteEnv {
- _dbgLevel :: DebugLevel
- _typeTranslator :: HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)
- _tcCache :: HashMap TyConOccName TyCon
- _tupleTcCache :: IntMap TyConName
- _evaluator :: PrimEvaluator
- _allowZero :: Bool
- _topEntities :: HashSet TmOccName
- typeTranslator :: Lens' RewriteEnv (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType))
- tupleTcCache :: Lens' RewriteEnv (IntMap TyConName)
- topEntities :: Lens' RewriteEnv (HashSet TmOccName)
- tcCache :: Lens' RewriteEnv (HashMap TyConOccName TyCon)
- evaluator :: Lens' RewriteEnv PrimEvaluator
- dbgLevel :: Lens' RewriteEnv DebugLevel
- allowZero :: Lens' RewriteEnv Bool
- newtype RewriteMonad extra a = R {
- runR :: RewriteEnv -> RewriteState extra -> (a, RewriteState extra, Any)
- type Transform m = [CoreContext] -> Term -> m Term
- type Rewrite extra = Transform (RewriteMonad extra)
Documentation
data CoreContext Source #
Context in which a term appears
AppFun | Function position of an application |
AppArg | Argument position of an application |
TyAppC | Function position of a type application |
LetBinding Id [Id] | RHS of a Let-binder with the sibling LHS' |
LetBody [Id] | Body of a Let-binding with the bound LHS' |
LamBody Id | Body of a lambda-term with the abstracted variable |
TyLamBody TyVar | Body of a TyLambda-term with the abstracted type-variable |
CaseAlt [Id] | RHS of a case-alternative with the variables bound by the pattern on the LHS |
CaseScrut | Subject of a case-decomposition |
CastBody | Body of a Cast |
Instances
Eq CoreContext Source # | |
(==) :: CoreContext -> CoreContext -> Bool # (/=) :: CoreContext -> CoreContext -> Bool # | |
Show CoreContext Source # | |
showsPrec :: Int -> CoreContext -> ShowS # show :: CoreContext -> String # showList :: [CoreContext] -> ShowS # |
data RewriteState extra Source #
State of a rewriting session
RewriteState | |
|
Instances
MonadState (RewriteState extra) (RewriteMonad extra) Source # | |
get :: RewriteMonad extra (RewriteState extra) # put :: RewriteState extra -> RewriteMonad extra () # state :: (RewriteState extra -> (a, RewriteState extra)) -> RewriteMonad extra a # |
uniqSupply :: forall extra. Lens' (RewriteState extra) Supply Source #
transformCounter :: forall extra. Lens' (RewriteState extra) Int Source #
nameCounter :: forall extra. Lens' (RewriteState extra) Int Source #
extra :: forall extra extra. Lens (RewriteState extra) (RewriteState extra) extra extra Source #
bindings :: forall extra. Lens' (RewriteState extra) BindingMap Source #
data RewriteEnv Source #
Read-only environment of a rewriting session
RewriteEnv | |
|
Instances
MonadReader RewriteEnv (RewriteMonad extra) Source # | |
ask :: RewriteMonad extra RewriteEnv # local :: (RewriteEnv -> RewriteEnv) -> RewriteMonad extra a -> RewriteMonad extra a # reader :: (RewriteEnv -> a) -> RewriteMonad extra a # |
typeTranslator :: Lens' RewriteEnv (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) Source #
tupleTcCache :: Lens' RewriteEnv (IntMap TyConName) Source #
topEntities :: Lens' RewriteEnv (HashSet TmOccName) Source #
tcCache :: Lens' RewriteEnv (HashMap TyConOccName TyCon) Source #
evaluator :: Lens' RewriteEnv PrimEvaluator Source #
dbgLevel :: Lens' RewriteEnv DebugLevel Source #
allowZero :: Lens' RewriteEnv Bool Source #
newtype RewriteMonad extra a Source #
Monad that keeps track how many transformations have been applied and can generate fresh variables and unique identifiers. In addition, it keeps track if a transformation/rewrite has been successfully applied.
R | |
|
Instances
type Transform m = [CoreContext] -> Term -> m Term Source #
Monadic action that transforms a term given a certain context
type Rewrite extra = Transform (RewriteMonad extra) Source #
A Transform
action in the context of the RewriteMonad