ghc-8.4.3: 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 #

Variable

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

Instances
Eq Var Source # 
Instance details

Defined in Var

Methods

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

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

Data Var Source # 
Instance details

Defined in 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 Source # 
Instance details

Defined in 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 #

OutputableBndr Var Source # 
Instance details

Defined in PprCore

Outputable Var Source # 
Instance details

Defined in Var

Methods

ppr :: Var -> SDoc Source #

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

Uniquable Var Source # 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique Source #

HasOccName Var Source # 
Instance details

Defined in Var

Methods

occName :: Var -> OccName Source #

NamedThing Var Source # 
Instance details

Defined in Var

type CoVar = Id Source #

Coercion Variable

type Id = Var Source #

Identifier

type NcId = Id Source #

 

type DictId = EvId Source #

Dictionary Identifier

type DFunId = Id Source #

Dictionary Function Identifier

type EvVar = EvId Source #

Evidence Variable

type EqVar = EvId Source #

Equality Variable

type EvId = Id Source #

Evidence Identifier

type IpId = EvId Source #

Implicit parameter Identifier

type JoinId = Id Source #

type TyVar = Var Source #

Type or kind Variable

type TypeVar = Var Source #

Type Variable

type KindVar = Var Source #

Kind Variable

type TKVar = Var Source #

Type or Kind Variable

type TyCoVar = Id Source #

Type or Coercion Variable

In and Out variants

type InVar = Var Source #

type InId = Id Source #

type OutId = Id 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

TyVar's

data TyVarBndr tyvar argf Source #

Constructors

TvBndr tyvar argf 
Instances
(Data tyvar, Data argf) => Data (TyVarBndr tyvar argf) Source # 
Instance details

Defined in Var

Methods

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

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

toConstr :: TyVarBndr tyvar argf -> Constr Source #

dataTypeOf :: TyVarBndr tyvar argf -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyVarBndr tyvar argf)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyVarBndr tyvar argf)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyVarBndr tyvar argf -> TyVarBndr tyvar argf Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBndr tyvar argf -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBndr tyvar argf -> r Source #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyVarBndr tyvar argf -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyVarBndr tyvar argf -> m (TyVarBndr tyvar argf) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBndr tyvar argf -> m (TyVarBndr tyvar argf) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBndr tyvar argf -> m (TyVarBndr tyvar argf) Source #

Outputable tv => Outputable (TyVarBndr tv ArgFlag) Source # 
Instance details

Defined in Var

Outputable tv => Outputable (TyVarBndr tv TyConBndrVis) Source # 
Instance details

Defined in TyCon

(Binary tv, Binary vis) => Binary (TyVarBndr tv vis) Source # 
Instance details

Defined in Var

Methods

put_ :: BinHandle -> TyVarBndr tv vis -> IO () Source #

put :: BinHandle -> TyVarBndr tv vis -> IO (Bin (TyVarBndr tv vis)) Source #

get :: BinHandle -> IO (TyVarBndr tv vis) Source #

data ArgFlag Source #

Argument Flag

Is something required to appear in source Haskell (Required), permitted by request (Specified) (visible type application), or prohibited entirely from appearing in source Haskell (Inferred)? See Note [TyVarBndrs, TyVarBinders, TyConBinders, and visibility] in TyCoRep

Constructors

Required 
Specified 
Inferred 
Instances
Eq ArgFlag Source # 
Instance details

Defined in Var

Methods

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

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

Data ArgFlag Source # 
Instance details

Defined in Var

Methods

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

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

toConstr :: ArgFlag -> Constr Source #

dataTypeOf :: ArgFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable ArgFlag Source # 
Instance details

Defined in Var

Binary ArgFlag Source # 
Instance details

Defined in Var

Outputable tv => Outputable (TyVarBndr tv ArgFlag) Source # 
Instance details

Defined in Var

type TyVarBinder = TyVarBndr TyVar ArgFlag Source #

Type Variable Binder

A TyVarBinder is the binder of a ForAllTy It's convenient to define this synonym here rather its natural home in TyCoRep, because it's used in DataCon.hs-boot

binderVar :: TyVarBndr tv argf -> tv Source #

binderVars :: [TyVarBndr tv argf] -> [tv] Source #

binderArgFlag :: TyVarBndr tv argf -> argf Source #

isVisibleArgFlag :: ArgFlag -> Bool Source #

Does this ArgFlag classify an argument that is written in Haskell?

isInvisibleArgFlag :: ArgFlag -> Bool Source #

Does this ArgFlag classify an argument that is not written in Haskell?

sameVis :: ArgFlag -> ArgFlag -> Bool Source #

Do these denote the same level of visibility? Required arguments are visible, others are not. So this function equates Specified and Inferred. Used for printing.

mkTyVarBinder :: ArgFlag -> Var -> TyVarBinder Source #

Make a named binder

mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder] Source #

Make many named binders

Constructing TyVar's

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]