ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

Var

Contents

Description

GHC uses several kinds of name internally:

These Var names may either be global or local, see Var

Global Ids and Vars are those that are imported or correspond to a data constructor, primitive operation, or record selectors. Local Ids and Vars are those bound within an expression (e.g. by a lambda) or at the top level of the module being compiled.

Synopsis

The main data type and synonyms

data Var Source #

Essentially a typed Name, that may also contain some additional information about the Var and it's use sites.

Instances

Eq Var # 

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Data Var # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var Source #

toConstr :: Var -> Constr Source #

dataTypeOf :: Var -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Var) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) Source #

gmapT :: (forall b. Data b => b -> b) -> Var -> Var Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var Source #

Ord Var # 

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Outputable Var # 

Methods

ppr :: Var -> SDoc Source #

pprPrec :: Rational -> Var -> SDoc Source #

Uniquable Var # 

Methods

getUnique :: Var -> Unique Source #

NamedThing Var # 
type PostRn Id ty # 
type PostRn Id ty = ty
type PostTc Id ty # 
type PostTc Id ty = ty

type CoVar = Id Source #

type Id = Var Source #

type NcId = Id Source #

type DFunId = Id Source #

type EvId = Id Source #

type IpId = EvId Source #

type TyVar = Var Source #

type TKVar = Var Source #

Taking Vars apart

varType :: Var -> Kind Source #

The type or kind of the Var in question

Modifying Vars

updateVarTypeM :: Monad m => (Type -> m Type) -> Id -> m Id Source #

Constructing, taking apart, modifying Ids

mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id Source #

Exported Vars will not be removed as dead code

globaliseId :: Id -> Id Source #

If it's a local, make it global

setIdExported :: Id -> Id Source #

Exports the given local Id. Can also be called on global Ids, such as data constructors and class operations, which are born as global Ids and automatically exported

setIdNotExported :: Id -> Id Source #

We can only do this to LocalIds

Predicates

isLocalVar :: Var -> Bool Source #

isLocalVar returns True for type variables as well as local Ids These are the variables that we need to pay attention to when finding free variables, or doing dependency analysis.

isExportedId :: Var -> Bool Source #

isExportedIdVar means "don't throw this away"

mustHaveLocalBinding :: Var -> Bool Source #

mustHaveLocalBinding returns True of Ids and TyVars that must have a binding in this module. The converse is not quite right: there are some global Ids that must have bindings, such as record selectors. But that doesn't matter, because it's only used for assertions

Constructing TyVars

Taking TyVars apart

Modifying TyVars

nonDetCmpVar :: Var -> Var -> Ordering Source #

Compare Vars by their Uniques. This is what Ord Var does, provided here to make it explicit at the call-site that it can introduce non-determinism. See Note [Unique Determinism]