clash-lib-0.6.6: CAES Language for Synchronous Hardware - As a Library

Safe HaskellNone
LanguageHaskell2010

CLaSH.Rewrite.Types

Description

Type and instance definitions for Rewrite modules

Synopsis

Documentation

data CoreContext Source

Context in which a term appears

Constructors

AppFun

Function position of an application

AppArg

Argument position of an application

TyAppC

Function position of a type application

LetBinding [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

Constructors

RewriteState 

Fields

_transformCounter :: !Int

Number of applied transformations

_bindings :: !(HashMap TmName (Type, Term))

Global binders

_uniqSupply :: !Supply

Supply of unique numbers

_curFun :: TmName

Function which is currently normalized

_nameCounter :: !Int

Used for Fresh

_extra :: !extra

Additional state

Instances

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

curFun :: forall extra. Lens' (RewriteState extra) TmName Source

bindings :: forall extra. Lens' (RewriteState extra) (HashMap TmName (Type, Term)) Source

data DebugLevel Source

Debug Message Verbosity

Constructors

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

Constructors

RewriteEnv 

Fields

_dbgLevel :: DebugLevel

Lvl at which we print debugging messages

_typeTranslator :: HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)

Hardcode Type -> HWType translator

_tcCache :: HashMap TyConName TyCon

TyCon cache

_tupleTcCache :: IntMap TyConName

Tuple TyCon cache

_evaluator :: HashMap TyConName TyCon -> Bool -> Term -> Term

Hardcoded evaluator (delta-reduction)}

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.

Constructors

R 

Fields

runR :: RewriteEnv -> RewriteState extra -> (a, RewriteState extra, Any)
 

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