Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A global typecheckable-thing, essentially anything that has a name.
Synopsis
- data TyThing
- class Monad m => MonadThings m where
- lookupThing :: Name -> m TyThing
- lookupId :: Name -> m Id
- lookupDataCon :: Name -> m DataCon
- lookupTyCon :: Name -> m TyCon
- mkATyCon :: TyCon -> TyThing
- mkAnId :: Id -> TyThing
- pprShortTyThing :: TyThing -> SDoc
- pprTyThingCategory :: TyThing -> SDoc
- tyThingCategory :: TyThing -> String
- implicitTyThings :: TyThing -> [TyThing]
- implicitConLikeThings :: ConLike -> [TyThing]
- implicitClassThings :: Class -> [TyThing]
- implicitTyConThings :: TyCon -> [TyThing]
- implicitCoTyCon :: TyCon -> [TyThing]
- isImplicitTyThing :: TyThing -> Bool
- tyThingParent_maybe :: TyThing -> Maybe TyThing
- tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
- tyThingAvailInfo :: TyThing -> [AvailInfo]
- tyThingTyCon :: HasDebugCallStack => TyThing -> TyCon
- tyThingCoAxiom :: HasDebugCallStack => TyThing -> CoAxiom Branched
- tyThingDataCon :: HasDebugCallStack => TyThing -> DataCon
- tyThingConLike :: HasDebugCallStack => TyThing -> ConLike
- tyThingId :: HasDebugCallStack => TyThing -> Id
Documentation
A global typecheckable-thing, essentially anything that has a name.
Not to be confused with a TcTyThing
, which is also a typecheckable
thing but in the *local* context. See GHC.Tc.Utils.Env for how to retrieve
a TyThing
given a Name
.
Instances
class Monad m => MonadThings m where Source #
Class that abstracts out the common ability of the monads in GHC
to lookup a TyThing
in the monadic environment by Name
. Provides
a number of related convenience functions for accessing particular
kinds of TyThing
lookupThing :: Name -> m TyThing Source #
lookupId :: Name -> m Id Source #
lookupDataCon :: Name -> m DataCon Source #
lookupTyCon :: Name -> m TyCon Source #
Instances
MonadThings CoreM Source # | |
MonadThings TcS Source # | |
MonadThings (IOEnv (Env DsGblEnv DsLclEnv)) Source # | |
MonadThings (IOEnv (Env TcGblEnv TcLclEnv)) Source # | |
MonadThings m => MonadThings (ReaderT s m) Source # | |
pprShortTyThing :: TyThing -> SDoc Source #
pprTyThingCategory :: TyThing -> SDoc Source #
tyThingCategory :: TyThing -> String Source #
implicitTyThings :: TyThing -> [TyThing] Source #
implicitConLikeThings :: ConLike -> [TyThing] Source #
implicitClassThings :: Class -> [TyThing] Source #
implicitTyConThings :: TyCon -> [TyThing] Source #
implicitCoTyCon :: TyCon -> [TyThing] Source #
isImplicitTyThing :: TyThing -> Bool Source #
Returns True
if there should be no interface-file declaration
for this thing on its own: either it is built-in, or it is part
of some other declaration, or it is generated implicitly by some
other declaration.
tyThingParent_maybe :: TyThing -> Maybe TyThing Source #
tyThingParent_maybe x returns (Just p) when pprTyThingInContext should print a declaration for p (albeit with some "..." in it) when asked to show x It returns the *immediate* parent. So a datacon returns its tycon but the tycon could be the associated type of a class, so it in turn might have a parent.
tyThingsTyCoVars :: [TyThing] -> TyCoVarSet Source #
tyThingAvailInfo :: TyThing -> [AvailInfo] Source #
The Names that a TyThing should bring into scope. Used to build the GlobalRdrEnv for the InteractiveContext.
tyThingTyCon :: HasDebugCallStack => TyThing -> TyCon Source #
tyThingCoAxiom :: HasDebugCallStack => TyThing -> CoAxiom Branched Source #
tyThingDataCon :: HasDebugCallStack => TyThing -> DataCon Source #
tyThingConLike :: HasDebugCallStack => TyThing -> ConLike Source #