ghc-8.2.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

Name

Contents

Description

GHC uses several kinds of name internally:

Names are one of:

  • External, if they name things declared in other modules. Some external Names are wired in, i.e. they name primitives defined in the compiler itself
  • Internal, if they name things in the module being compiled. Some internal Names are system names, if they are names manufactured by the compiler

Synopsis

The main types

data Name Source #

A unique, unambiguous name for something, containing information about where that thing originated.

Instances

Eq Name Source # 

Methods

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

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

Data Name Source # 

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

NFData Name Source # 

Methods

rnf :: Name -> () #

OutputableBndr Name Source # 
Outputable Name Source # 
Uniquable Name Source # 
Binary Name Source #

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

HasOccName Name Source # 

Methods

occName :: Name -> OccName Source #

NamedThing Name Source # 
type PostRn Name ty Source # 
type PostRn Name ty = ty
type PostTc Name ty Source # 

data BuiltInSyntax Source #

BuiltInSyntax is for things like (:), [] and tuples, which have special syntactic forms. They aren't in scope as such.

Constructors

BuiltInSyntax 
UserSyntax 

Creating Names

mkSystemName :: Unique -> OccName -> Name Source #

Create a name brought into being by the compiler

mkInternalName :: Unique -> OccName -> SrcSpan -> Name Source #

Create a name which is (for now at least) local to the current module and hence does not need a Module to disambiguate it from other Names

mkFCallName :: Unique -> String -> Name Source #

Make a name for a foreign call

mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name Source #

Create a name which definitely originates in the given module

mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name Source #

Create a name which is actually defined by the compiler itself

Manipulating and deconstructing Names

localiseName :: Name -> Name Source #

Make the Name into an internal name, regardless of what it was to begin with

mkLocalisedOccName :: Module -> (Maybe String -> OccName -> OccName) -> Name -> OccName Source #

Create a localised variant of a name.

If the name is external, encode the original's module name to disambiguate. SPJ says: this looks like a rather odd-looking function; but it seems to be used only during vectorisation, so I'm not going to worry

Predicates on Names

nameIsLocalOrFrom :: Module -> Name -> Bool Source #

Returns True if the name is (a) Internal (b) External but from the specified module (c) External but from the interactive package

The key idea is that False means: the entity is defined in some other module you can find the details (type, fixity, instances) in some interface file those details will be stored in the EPT or HPT

True means: the entity is defined in this module or earlier in the GHCi session you can find details (type, fixity, instances) in the TcGblEnv or TcLclEnv

The isInteractiveModule part is because successive interactions of a GCHi session each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come from the magic interactive package; and all the details are kept in the TcLclEnv, TcGblEnv, NOT in the HPT or EPT. See Note [The interactive package] in HscTypes

nameIsFromExternalPackage :: UnitId -> Name -> Bool Source #

Returns True if the Name comes from some other package: neither this pacakge nor the interactive package.

stableNameCmp :: Name -> Name -> Ordering Source #

Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.

Class NamedThing and overloaded friends

class NamedThing a where Source #

A class allowing convenient access to the Name of various datatypes

Minimal complete definition

getName

Methods

getOccName :: a -> OccName Source #

getName :: a -> Name Source #

Instances

NamedThing Name Source # 
NamedThing TyCon Source # 
NamedThing TyThing Source # 
NamedThing Var Source # 
NamedThing PatSyn Source # 
NamedThing DataCon Source # 
NamedThing ConLike Source # 
NamedThing Class Source # 
NamedThing FamInst Source # 
NamedThing IfaceConDecl Source # 
NamedThing IfaceClassOp Source # 
NamedThing IfaceDecl Source # 
NamedThing ClsInst Source # 
NamedThing (CoAxiom br) Source # 
NamedThing e => NamedThing (GenLocated l e) Source # 

nameStableString :: Name -> String Source #

Get a string representation of a Name that's unique and stable across recompilations. Used for deterministic generation of binds for derived instances. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"

module OccName