clash-lib-1.2.5: CAES Language for Synchronous Hardware - As a Library
Safe HaskellNone
LanguageHaskell2010

Clash.Core.VarEnv

Synopsis

Environment with variables as keys

type VarEnv a = UniqMap a Source #

Map indexed by variables

Accessors

Size information

nullVarEnv :: VarEnv a -> Bool Source #

Is the environment empty

Indexing

lookupVarEnv :: Var b -> VarEnv a -> Maybe a Source #

Look up a value based on the variable

lookupVarEnv' :: VarEnv a -> Var b -> a Source #

Lookup a value based on the variable

Errors out when the variable is not present

lookupVarEnvDirectly :: Unique -> VarEnv a -> Maybe a Source #

Lookup a value based on the unique of a variable

Construction

emptyVarEnv :: VarEnv a Source #

Empty map

unitVarEnv :: Var b -> a -> VarEnv a Source #

Environment containing a single variable-value pair

mkVarEnv :: [(Var a, b)] -> VarEnv b Source #

Create an environment given a list of var-value pairs

Modification

extendVarEnv :: Var b -> a -> VarEnv a -> VarEnv a Source #

Add a variable-value pair to the environment; overwrites the value if the variable already exists

extendVarEnvList :: VarEnv a -> [(Var b, a)] -> VarEnv a Source #

Add a list of variable-value pairs; the values of existing keys will be overwritten

extendVarEnvWith :: Var b -> a -> (a -> a -> a) -> VarEnv a -> VarEnv a Source #

Add a variable-value pair to the environment; if the variable already exists, the two values are merged with the given function

delVarEnv :: VarEnv a -> Var b -> VarEnv a Source #

Remove a variable-value pair from the environment

delVarEnvList :: VarEnv a -> [Var b] -> VarEnv a Source #

Remove a list of variable-value pairs from the environment

unionVarEnv :: VarEnv a -> VarEnv a -> VarEnv a Source #

Get the (left-biased) union of two environments

unionVarEnvWith :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a Source #

Get the union of two environments, mapped values existing in both environments will be merged with the given function.

Element-wise operations

Mapping

mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b Source #

Apply a function to every element in the environment

mapMaybeVarEnv :: (a -> Maybe b) -> VarEnv a -> VarEnv b Source #

Apply a function to every element in the environment; values for which the function returns Nothing are removed from the environment

Folding

foldlWithUniqueVarEnv' :: (a -> Unique -> b -> a) -> a -> VarEnv b -> a Source #

Strict left-fold over an environment using both the unique of the the variable and the value

Working with predicates

Searching

elemVarEnv :: Var a -> VarEnv b -> Bool Source #

Does the variable exist in the environment

notElemVarEnv :: Var a -> VarEnv b -> Bool Source #

Does the variable not exist in the environment

Conversions

Lists

eltsVarEnv :: VarEnv a -> [a] Source #

Extract the elements

Sets of variables

type VarSet = UniqSet (Var Any) Source #

Set of variables

Construction

emptyVarSet :: VarSet Source #

The empty set

unitVarSet :: Var a -> VarSet Source #

The set of a single variable

Modification

delVarSetByKey :: Unique -> VarSet -> VarSet Source #

Remove a variable from the set based on its Unique

unionVarSet :: VarSet -> VarSet -> VarSet Source #

Union two sets

Working with predicates

Searching

elemVarSet :: Var a -> VarSet -> Bool Source #

Is the variable an element in the set

notElemVarSet :: Var a -> VarSet -> Bool Source #

Is the variable not an element in the set

Conversions

Lists

mkVarSet :: [Var a] -> VarSet Source #

Create a set from a list of variables

In-scope sets

data InScopeSet Source #

Set of variables that is in scope at some point

The Int is a kind of hash-value used to generate new uniques. It should never be zero

See "Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 for the motivation

Instances

Instances details
Generic InScopeSet Source # 
Instance details

Defined in Clash.Core.VarEnv

Associated Types

type Rep InScopeSet :: Type -> Type #

Binary InScopeSet Source # 
Instance details

Defined in Clash.Core.VarEnv

ClashPretty InScopeSet Source # 
Instance details

Defined in Clash.Core.VarEnv

type Rep InScopeSet Source # 
Instance details

Defined in Clash.Core.VarEnv

type Rep InScopeSet = D1 ('MetaData "InScopeSet" "Clash.Core.VarEnv" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "InScopeSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarSet) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))

Accessors

Size information

Indexing

lookupInScope :: InScopeSet -> Var a -> Maybe (Var Any) Source #

Look up a variable in the InScopeSet. This gives you the canonical version of the variable

Construction

mkInScopeSet :: VarSet -> InScopeSet Source #

Create a set of variables in scope

Modification

extendInScopeSetList :: InScopeSet -> [Var a] -> InScopeSet Source #

Add a list of variables in scope

unionInScope :: InScopeSet -> InScopeSet -> InScopeSet Source #

Union two sets of in scope variables

Working with predicates

Searching

elemInScopeSet :: Var a -> InScopeSet -> Bool Source #

Is the variable in scope

elemUniqInScopeSet :: Unique -> InScopeSet -> Bool Source #

Check whether an element exists in the set based on the Unique contained in that element

notElemInScopeSet :: Var a -> InScopeSet -> Bool Source #

Is the variable not in scope

varSetInScope :: VarSet -> InScopeSet -> Bool Source #

Is the set of variables in scope

Unique generation

uniqAway :: (Uniquable a, ClashPretty a) => InScopeSet -> a -> a Source #

Ensure that the Unique of a variable does not occur in the InScopeSet

uniqAway' Source #

Arguments

:: (Uniquable a, ClashPretty a) 
=> (Unique -> Bool)

Unique in scope test

-> Int

Seed

-> a 
-> a 

Dual renaming

data RnEnv Source #

Rename environment for e.g. alpha equivalence

When going under binders for e.g.

x -> e1  aeq y -> e2

We want to rename [x -> y] or [y -> x], but we have to pick a binder that is neither free in e1 nor e2 or we risk accidental capture.

So we must maintain:

  1. A renaming for the left term
  2. A renaming for the right term
  3. A set of in scope variables

Construction

mkRnEnv :: InScopeSet -> RnEnv Source #

Create an empty renaming environment

Renaming

rnTmBndr :: RnEnv -> Id -> Id -> RnEnv Source #

Simultaneously go under the binder bL and binder bR, finds a new binder newTvB, and return an environment mapping [bL -> newB] and [bR -> newB]

rnTyBndr :: RnEnv -> TyVar -> TyVar -> RnEnv Source #

Simultaneously go under the type-variable binder bTvL and type-variable binder bTvR, finds a new binder newTvB, and return an environment mapping [bTvL -> newB] and [bTvR -> newB]

rnTmBndrs :: RnEnv -> [Id] -> [Id] -> RnEnv Source #

Applies rnTmBndr to several variables: the two variable lists must be of equal length.

rnTyBndrs :: RnEnv -> [TyVar] -> [TyVar] -> RnEnv Source #

Applies rnTyBndr to several variables: the two variable lists must be of equal length.

rnOccLId :: RnEnv -> Id -> Id Source #

Look up the renaming of an occurrence in the left term

rnOccRId :: RnEnv -> Id -> Id Source #

Look up the renaming of an occurrence in the left term

rnOccLTy :: RnEnv -> TyVar -> TyVar Source #

Look up the renaming of an type-variable occurrence in the left term

rnOccRTy :: RnEnv -> TyVar -> TyVar Source #

Look up the renaming of an type-variable occurrence in the right term