clash-lib-1.0.0: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2012-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.FreeVars

Description

Free variable calculations

Synopsis

Free variable calculation

typeFreeVars :: Fold Type TyVar Source #

Gives the free type-variables in a Type, implemented as a Fold

The Fold is closed over the types of its variables, so:

foldMapOf typeFreeVars unitVarSet ((a:* -> k) Int) = {a, k}

termFreeVarsX :: Fold Term (Var a) Source #

Gives the free variables of a Term, implemented as a Fold

The Fold is closed over the types of variables, so:

foldMapOf termFreeVars unitVarSet (case (x : (a:* -> k) Int)) of {}) = {x, a, k}

NB this collects both global and local IDs, and you almost NEVER want to use this. Use one of the other FV calculations instead

freeIds :: Fold Term Id Source #

Gives the free identifiers of a Term, implemented as a Fold

freeLocalVars :: Fold Term (Var a) Source #

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

freeLocalIds :: Fold Term Id Source #

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

globalIds :: Fold Term Id Source #

Calculate the global free identifiers of an expression: the free identifiers that are bound in the global environment.

termFreeTyVars :: Fold Term TyVar Source #

Gives the free type-variables of a Term, implemented as a Fold

The Fold is closed over the types of variables, so:

foldMapOf termFreeTyVars unitVarSet (case (x : (a:* -> k) Int)) of {}) = {a, k}

tyFVsOfTypes :: Foldable f => f Type -> VarSet Source #

Collect the free variables of a collection of type into a set

localFVsOfTerms :: Foldable f => f Term -> VarSet Source #

Collect the free variables of a collection of terms into a set

hasLocalFreeVars :: Term -> Bool Source #

Determines if term has any locally free variables. That is, the free type variables and the free identifiers that are not bound in the global scope.

Fast

noFreeVarsOfType :: Type -> Bool Source #

Determine whether a type has no free type variables.

occurrence check

localIdOccursIn :: Id -> Term -> Bool Source #

Check whether a local identifier occurs free in a term

globalIdOccursIn :: Id -> Term -> Bool Source #

Check whether a local identifier occurs free in a term

localIdDoesNotOccurIn :: Id -> Term -> Bool Source #

Check whether an identifier does not occur free in a term

localIdsDoNotOccurIn :: [Id] -> Term -> Bool Source #

Check whether a set of identifiers does not occur free in a term

localVarsDoNotOccurIn :: [Var a] -> Term -> Bool Source #

Check whether a set of variables does not occur free in a term

Internal

typeFreeVars' Source #

Arguments

:: (Contravariant f, Applicative f) 
=> (forall b. Var b -> Bool)

Predicate telling whether a variable is interesting

-> IntSet

Uniques of the variables in scope, used by termFreeVars'

-> (Var a -> f (Var a)) 
-> Type 
-> f Type 

Gives the "interesting" free variables in a Type, implemented as a Fold

The Fold is closed over the types of variables, so:

foldMapOf (typeFreeVars' (const True) IntSet.empty) unitVarSet ((a:* -> k) Int) = {a, k}

Note [Closing over kind variables]

Consider the type

forall k . b -> k

where

b :: k -> Type

When we close over the free variables of forall k . b -> k, i.e. b, then the k in b :: k -> Type is most definitely not the k in forall k . b -> k. So when a type variable is free, i.e. not in the inScope set, its kind variables also aren´t; so in order to prevent collisions due to shadowing we close using an empty inScope set.

See also: https://git.haskell.org/ghc.git/commitdiff/503514b94f8dc7bd9eab5392206649aee45f140b

termFreeVars' Source #

Arguments

:: (Contravariant f, Applicative f) 
=> (forall b. Var b -> Bool)

Predicate telling whether a variable is interesting

-> (Var a -> f (Var a)) 
-> Term 
-> f Term 

Gives the "interesting" free variables in a Term, implemented as a Fold

The Fold is closed over the types of variables, so:

foldMapOf (termFreeVars' (const True)) unitVarSet (case (x : (a:* -> k) Int)) of {}) = {x, a, k}

Note [Closing over type variables]

Consider the term

/\(k :: Type) -> \(b :: k) -> a

where

a :: k

When we close over the free variables of /k -> (b :: k) -> (a :: k), i.e. a, then the k in a :: k is most definitely not the k in introduced by the /k ->. So when a term variable is free, i.e. not in the inScope set, its type variables also aren´t; so in order to prevent collisions due to shadowing we close using an empty inScope set.

See also: https://git.haskell.org/ghc.git/commitdiff/503514b94f8dc7bd9eab5392206649aee45f140b