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

Safe HaskellNone
LanguageHaskell2010

CLaSH.Rewrite.Util

Description

Utilities for rewriting: e.g. inlining, specialisation, etc.

Synopsis

Documentation

liftR :: Monad m => m a -> RewriteMonad m a Source

Lift an action working in the inner monad to the RewriteMonad

liftRS :: Monad m => m a -> RewriteSession m a Source

Lift an action working in the inner monad to the RewriteSession

apply Source

Arguments

:: (Monad m, Functor m) 
=> String

Name of the transformation

-> Rewrite m

Transformation to be applied

-> Rewrite m 

Record if a transformation is succesfully applied

runRewrite Source

Arguments

:: (Monad m, Functor m) 
=> String

Name of the transformation

-> Rewrite m

Transformation to perform

-> Term

Term to transform

-> RewriteSession m Term 

Perform a transformation on a Term

runRewriteSession :: (Functor m, Monad m) => DebugLevel -> RewriteState -> RewriteSession m a -> m a Source

Evaluate a RewriteSession to its inner monad

setChanged :: Monad m => RewriteMonad m () Source

Notify that a transformation has changed the expression

changed :: Monad m => a -> RewriteMonad m a Source

Identity function that additionally notifies that a transformation has changed the expression

contextEnv :: [CoreContext] -> (Gamma, Delta) Source

Create a type and kind context out of a transformation context

mkEnv :: (Functor m, Monad m) => [CoreContext] -> RewriteMonad m (Gamma, Delta) Source

Create a complete type and kind context out of the global binders and the transformation context

mkTmBinderFor Source

Arguments

:: (Functor m, Fresh m, MonadUnique m) 
=> HashMap TyConName TyCon

TyCon cache

-> String

Name of the new binder

-> Term

Term to bind

-> m (Id, Term) 

Make a new binder and variable reference for a term

mkBinderFor Source

Arguments

:: (Functor m, Monad m, MonadUnique m, Fresh m) 
=> HashMap TyConName TyCon

TyCon cache

-> String

Name of the new binder

-> Either Term Type

Type or Term to bind

-> m (Either (Id, Term) (TyVar, Type)) 

Make a new binder and variable reference for either a term or a type

mkInternalVar Source

Arguments

:: (Functor m, Monad m, MonadUnique m) 
=> String

Name of the identifier

-> KindOrType 
-> m (Id, Term) 

Make a new, unique, identifier and corresponding variable reference

inlineBinders Source

Arguments

:: Monad m 
=> (LetBinding -> RewriteMonad m Bool)

Property test

-> Rewrite m 

Inline the binders in a let-binding that have a certain property

substituteBinders Source

Arguments

:: [LetBinding]

Let-binders to substitute

-> [LetBinding]

Let-binders where substitution takes place

-> Term

Expression where substitution takes place

-> ([LetBinding], Term) 

Substitute the RHS of the first set of Let-binders for references to the first set of Let-binders in: the second set of Let-binders and the additional term

localFreeVars :: (Functor m, Monad m, Collection c) => Term -> RewriteMonad m (c TyName, c TmName) Source

Calculate the local free variable of an expression: the free variables that are not bound in the global environment.

liftBinders Source

Arguments

:: (Functor m, Monad m) 
=> (LetBinding -> RewriteMonad m Bool)

Property test

-> Rewrite m 

Lift the binders in a let-binding to a global function that have a certain property

liftBinding :: (Functor m, Monad m) => Gamma -> Delta -> LetBinding -> RewriteMonad m LetBinding Source

Create a global function for a Let-binding and return a Let-binding where the RHS is a reference to the new global function applied to the free variables of the original RHS

mkFunction Source

Arguments

:: (Functor m, Monad m) 
=> TmName

Name of the function

-> Term

Term bound to the function

-> RewriteMonad m (TmName, Type)

Name with a proper unique and the type of the function

Make a global function for a name-term tuple

addGlobalBind :: (Functor m, Monad m) => TmName -> Type -> Term -> RewriteMonad m () Source

Add a function to the set of global binders

cloneVar :: (Functor m, Monad m) => TmName -> RewriteMonad m TmName Source

Create a new name out of the given name, but with another unique

isLocalVar :: (Functor m, Monad m) => Term -> RewriteMonad m Bool Source

Test whether a term is a variable reference to a local binder

isUntranslatable :: (Functor m, Monad m) => Term -> RewriteMonad m Bool Source

Determine if a term cannot be represented in hardware

isLambdaBodyCtx :: CoreContext -> Bool Source

Is the Context a Lambda/Term-abstraction context?

mkWildValBinder :: (Functor m, Monad m, MonadUnique m) => Type -> m Id Source

Make a binder that should not be referenced

mkSelectorCase Source

Arguments

:: (Functor m, Monad m, MonadUnique m, Fresh m) 
=> String

Name of the caller of this function

-> HashMap TyConName TyCon

TyCon cache

-> [CoreContext]

Transformation Context in which this function is called

-> Term

Subject of the case-composition

-> Int 
-> Int 
-> m Term 

Make a case-decomposition that extracts a field out of a (Sum-of-)Product type

specialise Source

Arguments

:: (Functor m, MonadState s m) 
=> Lens' s (Map (TmName, Int, Either Term Type) (TmName, Type))

Lens into previous specialisations

-> Lens' s (HashMap TmName Int)

Lens into the specialisation history

-> Lens' s Int

Lens into the specialisation limit

-> Bool 
-> Rewrite m 

Specialise an application on its argument

specialise' Source

Arguments

:: (Functor m, MonadState s m) 
=> Lens' s (Map (TmName, Int, Either Term Type) (TmName, Type))

Lens into previous specialisations

-> Lens' s (HashMap TmName Int)

Lens into specialisation history

-> Lens' s Int

Lens into the specialisation limit

-> Bool

Perform specialisation limit check

-> [CoreContext] 
-> Term

Original term

-> (Term, [Either Term Type])

Function part of the term, split into root and applied arguments

-> Either Term Type

Argument to specialize on

-> R m Term 

Specialise an application on its argument

specArgBndrsAndVars :: (Functor m, Monad m) => [CoreContext] -> Either Term Type -> RewriteMonad m ([Either Id TyVar], [Either Term Type]) Source

Create binders and variable references for free variables in specArg