Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC uses several kinds of name internally:
OccName
: see OccNameRdrName
: see RdrNameName
: see NameId
: see IdVar
is a synonym for theId
type but it may additionally potentially contain type variables, which have aKind
rather than aType
and only contain some extra details during typechecking.
These Var
names may either be global or local, see Var
Global Id
s and Var
s are those that are imported or correspond
to a data constructor, primitive operation, or record selectors.
Local Id
s and Var
s are those bound within an expression
(e.g. by a lambda) or at the top level of the module being compiled.
Synopsis
- data Var
- type CoVar = Id
- type Id = Var
- type NcId = Id
- type DictId = EvId
- type DFunId = Id
- type EvVar = EvId
- type EqVar = EvId
- type EvId = Id
- type IpId = EvId
- type JoinId = Id
- type TyVar = Var
- type TcTyVar = Var
- type TypeVar = Var
- type KindVar = Var
- type TKVar = Var
- type TyCoVar = Id
- type InVar = Var
- type InCoVar = CoVar
- type InId = Id
- type InTyVar = TyVar
- type OutVar = Var
- type OutCoVar = CoVar
- type OutId = Id
- type OutTyVar = TyVar
- varName :: Var -> Name
- varUnique :: Var -> Unique
- varType :: Var -> Kind
- setVarName :: Var -> Name -> Var
- setVarUnique :: Var -> Unique -> Var
- setVarType :: Id -> Type -> Id
- updateVarType :: (Type -> Type) -> Id -> Id
- updateVarTypeM :: Monad m => (Type -> m Type) -> Id -> m Id
- mkGlobalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkCoVar :: Name -> Type -> CoVar
- idInfo :: HasDebugCallStack => Id -> IdInfo
- idDetails :: Id -> IdDetails
- lazySetIdInfo :: Id -> IdInfo -> Var
- setIdDetails :: Id -> IdDetails -> Id
- globaliseId :: Id -> Id
- setIdExported :: Id -> Id
- setIdNotExported :: Id -> Id
- isId :: Var -> Bool
- isTyVar :: Var -> Bool
- isTcTyVar :: Var -> Bool
- isLocalVar :: Var -> Bool
- isLocalId :: Var -> Bool
- isCoVar :: Var -> Bool
- isNonCoVarId :: Var -> Bool
- isTyCoVar :: Var -> Bool
- isGlobalId :: Var -> Bool
- isExportedId :: Var -> Bool
- mustHaveLocalBinding :: Var -> Bool
- data TyVarBndr tyvar argf = TvBndr tyvar argf
- data ArgFlag
- type TyVarBinder = TyVarBndr TyVar ArgFlag
- binderVar :: TyVarBndr tv argf -> tv
- binderVars :: [TyVarBndr tv argf] -> [tv]
- binderArgFlag :: TyVarBndr tv argf -> argf
- binderKind :: TyVarBndr TyVar argf -> Kind
- isVisibleArgFlag :: ArgFlag -> Bool
- isInvisibleArgFlag :: ArgFlag -> Bool
- sameVis :: ArgFlag -> ArgFlag -> Bool
- mkTyVarBinder :: ArgFlag -> Var -> TyVarBinder
- mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder]
- mkTyVar :: Name -> Kind -> TyVar
- mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
- tyVarName :: TyVar -> Name
- tyVarKind :: TyVar -> Kind
- tcTyVarDetails :: TyVar -> TcTyVarDetails
- setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar
- setTyVarName :: TyVar -> Name -> TyVar
- setTyVarUnique :: TyVar -> Unique -> TyVar
- setTyVarKind :: TyVar -> Kind -> TyVar
- updateTyVarKind :: (Kind -> Kind) -> TyVar -> TyVar
- updateTyVarKindM :: Monad m => (Kind -> m Kind) -> TyVar -> m TyVar
- nonDetCmpVar :: Var -> Var -> Ordering
The main data type and synonyms
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and it's use sites.
Instances
Eq Var # | |
Data Var # | |
Defined in Var 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 # | |
OutputableBndr Var # | |
Outputable Var # | |
Uniquable Var # | |
HasOccName Var # | |
NamedThing Var # | |
In and Out variants
Taking Var
s apart
Modifying Var
s
Constructing, taking apart, modifying Id
s
mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id Source #
Exported Var
s will not be removed as dead code
globaliseId :: Id -> Id Source #
If it's a local, make it global
setIdExported :: Id -> Id Source #
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 Id
s
These are the variables that we need to pay attention to when finding free
variables, or doing dependency analysis.
isNonCoVarId :: Var -> Bool Source #
isGlobalId :: Var -> Bool Source #
isExportedId :: Var -> Bool Source #
isExportedIdVar
means "don't throw this away"
mustHaveLocalBinding :: Var -> Bool Source #
mustHaveLocalBinding
returns True
of Id
s and TyVar
s
that must have a binding in this module. The converse
is not quite right: there are some global Id
s 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 #
TvBndr tyvar argf |
Instances
(Data tyvar, Data argf) => Data (TyVarBndr tyvar argf) # | |
Defined in Var 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) # | |
Outputable tv => Outputable (TyVarBndr tv TyConBndrVis) # | |
(Binary tv, Binary vis) => Binary (TyVarBndr tv vis) # | |
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
Instances
Eq ArgFlag # | |
Data ArgFlag # | |
Defined in Var 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 # | |
Ord ArgFlag # | |
Outputable ArgFlag # | |
Binary ArgFlag # | |
Outputable tv => Outputable (TyVarBndr tv ArgFlag) # | |
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
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?
mkTyVarBinder :: ArgFlag -> Var -> TyVarBinder Source #
Make a named binder
mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder] Source #
Make many named binders
Constructing TyVar's
Taking TyVar
s apart
tcTyVarDetails :: TyVar -> TcTyVarDetails Source #
setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar Source #