ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Name

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

Instances details
Data Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

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

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

toConstr :: Name -> Constr Source #

dataTypeOf :: Name -> DataType Source #

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

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

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

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

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

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

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

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

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

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

NFData Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () Source #

NamedThing Name Source # 
Instance details

Defined in GHC.Types.Name

HasOccName Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName Source #

Uniquable Name Source # 
Instance details

Defined in GHC.Types.Name

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.

Instance details

Defined in GHC.Types.Name

Outputable Name Source # 
Instance details

Defined in GHC.Types.Name

OutputableBndr Name Source # 
Instance details

Defined in GHC.Types.Name

Eq Name Source #

The same comments as for Name's Ord instance apply.

Instance details

Defined in GHC.Types.Name

Methods

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

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

Ord Name Source #

Caution: This instance is implemented via nonDetCmpUnique, which means that the ordering is not stable across deserialization or rebuilds.

See nonDetCmpUnique for further information, and trac #15240 for a bug caused by improper use of this instance.

Instance details

Defined in GHC.Types.Name

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 #

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

Predicates on Names

isDynLinkName :: Platform -> Module -> Name -> Bool Source #

Will the Name come from a dynamically linked package?

isWiredIn :: NamedThing thing => thing -> Bool Source #

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 GHCi 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 GHC.Driver.Types

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

Returns True if the Name comes from some other package: neither this package 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

Instances details
NamedThing Class Source # 
Instance details

Defined in GHC.Core.Class

NamedThing ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

NamedThing DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

NamedThing FamInst Source # 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

NamedThing PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

NamedThing TyThing Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

NamedThing TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

NamedThing IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

NamedThing Name Source # 
Instance details

Defined in GHC.Types.Name

NamedThing Var Source # 
Instance details

Defined in GHC.Types.Var

NamedThing (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

NamedThing (HsTyVarBndr flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

NamedThing tv => NamedThing (VarBndr tv flag) Source # 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName Source #

getName :: VarBndr tv flag -> Name Source #

pprNameUnqualified :: Name -> SDoc Source #

Print the string of Name unqualifiedly directly.

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"