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 |
Type and instance definitions for Rewrite modules
- data CoreContext
- data RewriteState extra = RewriteState {}
- 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) (HashMap TmName (Type, SrcSpan, Term))
- data DebugLevel
- data RewriteEnv = RewriteEnv {}
- typeTranslator :: Lens' RewriteEnv (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType))
- tupleTcCache :: Lens' RewriteEnv (IntMap TyConName)
- tcCache :: Lens' RewriteEnv (HashMap TyConName TyCon)
- evaluator :: Lens' RewriteEnv (HashMap TyConName TyCon -> Bool -> Term -> Term)
- dbgLevel :: Lens' RewriteEnv DebugLevel
- 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 |
data RewriteState extra Source
State of a rewriting session
RewriteState | |
|
MonadState (RewriteState extra) (RewriteMonad extra) Source |
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
data DebugLevel Source
Debug Message Verbosity
DebugNone | Don't show debug messages |
DebugFinal | Show completely normalized expressions |
DebugName | Names of applied transformations |
DebugApplied | Show sub-expressions after a successful rewrite |
DebugAll | Show all sub-expressions on which a rewrite is attempted |
data RewriteEnv Source
Read-only environment of a rewriting session
RewriteEnv | |
|
MonadReader RewriteEnv (RewriteMonad extra) Source |
typeTranslator :: Lens' RewriteEnv (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) 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 | |
|
MonadReader RewriteEnv (RewriteMonad extra) Source | |
MonadWriter Any (RewriteMonad extra) Source | |
Monad (RewriteMonad extra) Source | |
Functor (RewriteMonad extra) Source | |
MonadFix (RewriteMonad extra) Source | |
Applicative (RewriteMonad extra) Source | |
Fresh (RewriteMonad extra) Source | |
MonadUnique (RewriteMonad extra) Source | |
MonadState (RewriteState extra) (RewriteMonad extra) Source |
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