| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Clash.Core.VarEnv
Synopsis
- type VarEnv a = UniqMap a
- nullVarEnv :: VarEnv a -> Bool
- lookupVarEnv :: Var b -> VarEnv a -> Maybe a
- lookupVarEnv' :: VarEnv a -> Var b -> a
- lookupVarEnvDirectly :: Unique -> VarEnv a -> Maybe a
- emptyVarEnv :: VarEnv a
- unitVarEnv :: Var b -> a -> VarEnv a
- mkVarEnv :: [(Var a, b)] -> VarEnv b
- extendVarEnv :: Var b -> a -> VarEnv a -> VarEnv a
- extendVarEnvList :: VarEnv a -> [(Var b, a)] -> VarEnv a
- extendVarEnvWith :: Var b -> a -> (a -> a -> a) -> VarEnv a -> VarEnv a
- delVarEnv :: VarEnv a -> Var b -> VarEnv a
- delVarEnvList :: VarEnv a -> [Var b] -> VarEnv a
- unionVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
- unionVarEnvWith :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
- mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b
- mapMaybeVarEnv :: (a -> Maybe b) -> VarEnv a -> VarEnv b
- foldlWithUniqueVarEnv' :: (a -> Unique -> b -> a) -> a -> VarEnv b -> a
- elemVarEnv :: Var a -> VarEnv b -> Bool
- notElemVarEnv :: Var a -> VarEnv b -> Bool
- eltsVarEnv :: VarEnv a -> [a]
- type VarSet = UniqSet (Var Any)
- emptyVarSet :: VarSet
- unitVarSet :: Var a -> VarSet
- delVarSetByKey :: Unique -> VarSet -> VarSet
- unionVarSet :: VarSet -> VarSet -> VarSet
- elemVarSet :: Var a -> VarSet -> Bool
- notElemVarSet :: Var a -> VarSet -> Bool
- mkVarSet :: [Var a] -> VarSet
- eltsVarSet :: VarSet -> [Var Any]
- data InScopeSet
- emptyInScopeSet :: InScopeSet
- lookupInScope :: InScopeSet -> Var a -> Maybe (Var Any)
- mkInScopeSet :: VarSet -> InScopeSet
- extendInScopeSet :: InScopeSet -> Var a -> InScopeSet
- extendInScopeSetList :: InScopeSet -> [Var a] -> InScopeSet
- unionInScope :: InScopeSet -> InScopeSet -> InScopeSet
- elemInScopeSet :: Var a -> InScopeSet -> Bool
- notElemInScopeSet :: Var a -> InScopeSet -> Bool
- varSetInScope :: VarSet -> InScopeSet -> Bool
- uniqAway :: (Uniquable a, ClashPretty a) => InScopeSet -> a -> a
- uniqAway' :: (Uniquable a, ClashPretty a) => (Unique -> Bool) -> Int -> a -> a
- data RnEnv
- mkRnEnv :: InScopeSet -> RnEnv
- rnTmBndr :: RnEnv -> Id -> Id -> RnEnv
- rnTyBndr :: RnEnv -> TyVar -> TyVar -> RnEnv
- rnTmBndrs :: RnEnv -> [Id] -> [Id] -> RnEnv
- rnTyBndrs :: RnEnv -> [TyVar] -> [TyVar] -> RnEnv
- rnOccLId :: RnEnv -> Id -> Id
- rnOccRId :: RnEnv -> Id -> Id
- rnOccLTy :: RnEnv -> TyVar -> TyVar
- rnOccRTy :: RnEnv -> TyVar -> TyVar
Environment with variables as keys
Accessors
Size information
nullVarEnv :: VarEnv a -> Bool Source #
Is the environment empty
Indexing
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
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
Conversions
Lists
eltsVarEnv :: VarEnv a -> [a] Source #
Extract the elements
Sets 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
Working with predicates
Searching
Conversions
Lists
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
| Generic InScopeSet Source # | |
| Defined in Clash.Core.VarEnv Associated Types type Rep InScopeSet :: Type -> Type # | |
| Binary InScopeSet Source # | |
| Defined in Clash.Core.VarEnv | |
| ClashPretty InScopeSet Source # | |
| Defined in Clash.Core.VarEnv Methods clashPretty :: InScopeSet -> Doc () Source # | |
| type Rep InScopeSet Source # | |
| Defined in Clash.Core.VarEnv type Rep InScopeSet = D1 (MetaData "InScopeSet" "Clash.Core.VarEnv" "clash-lib-1.2.0-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
emptyInScopeSet :: InScopeSet Source #
The empty set
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
extendInScopeSet :: InScopeSet -> Var a -> InScopeSet Source #
The empty set
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
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
Arguments
| :: (Uniquable a, ClashPretty a) | |
| => (Unique -> Bool) | Unique in scope test | 
| -> Int | Seed | 
| -> a | |
| -> a | 
Dual renaming
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:
- A renaming for the left term
- A renaming for the right term
- 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.