Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC uses several kinds of name internally:
OccName
: see OccNameRdrName
: see RdrNameName
is the type of names that have had their scoping and binding resolved. They have anOccName
but also aUnique
that disambiguates Names that have the sameOccName
and indeed is used for allName
comparison. Names also contain information about where they originated from, see NameId
: see IdVar
: see Var
- 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
- data Name
- data BuiltInSyntax
- mkSystemName :: Unique -> OccName -> Name
- mkSystemNameAt :: Unique -> OccName -> SrcSpan -> Name
- mkInternalName :: Unique -> OccName -> SrcSpan -> Name
- mkClonedInternalName :: Unique -> Name -> Name
- mkDerivedInternalName :: (OccName -> OccName) -> Unique -> Name -> Name
- mkSystemVarName :: Unique -> FastString -> Name
- mkSysTvName :: Unique -> FastString -> Name
- mkFCallName :: Unique -> String -> Name
- mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
- mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name
- nameUnique :: Name -> Unique
- setNameUnique :: Name -> Unique -> Name
- nameOccName :: Name -> OccName
- nameModule :: Name -> Module
- nameModule_maybe :: Name -> Maybe Module
- setNameLoc :: Name -> SrcSpan -> Name
- tidyNameOcc :: Name -> OccName -> Name
- localiseName :: Name -> Name
- mkLocalisedOccName :: Module -> (Maybe String -> OccName -> OccName) -> Name -> OccName
- nameSrcLoc :: Name -> SrcLoc
- nameSrcSpan :: Name -> SrcSpan
- pprNameDefnLoc :: Name -> SDoc
- pprDefinedAt :: Name -> SDoc
- isSystemName :: Name -> Bool
- isInternalName :: Name -> Bool
- isExternalName :: Name -> Bool
- isTyVarName :: Name -> Bool
- isTyConName :: Name -> Bool
- isDataConName :: Name -> Bool
- isValName :: Name -> Bool
- isVarName :: Name -> Bool
- isWiredInName :: Name -> Bool
- isBuiltInSyntax :: Name -> Bool
- wiredInNameTyThing_maybe :: Name -> Maybe TyThing
- nameIsLocalOrFrom :: Module -> Name -> Bool
- stableNameCmp :: Name -> Name -> Ordering
- class NamedThing a where
- getOccName :: a -> OccName
- getName :: a -> Name
- getSrcLoc :: NamedThing a => a -> SrcLoc
- getSrcSpan :: NamedThing a => a -> SrcSpan
- getOccString :: NamedThing a => a -> String
- pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc
- pprPrefixName :: (Outputable a, NamedThing a) => a -> SDoc
- pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
- module OccName
The main types
A unique, unambigious name for something, containing information about where that thing originated.
Eq Name | |
Data Name | |
Ord Name | |
OutputableBndr Name | |
Outputable Name | |
Uniquable Name | |
Binary Name | |
HasOccName Name | |
NamedThing Name | |
type PostRn Name ty = ty | |
type PostTc Name ty = PlaceHolder |
data BuiltInSyntax Source
BuiltInSyntax is for things like (:)
, []
and tuples,
which have special syntactic forms. They aren't in scope
as such.
Creating Name
s
mkSystemName :: Unique -> OccName -> Name Source
Create a name brought into being by the compiler
mkClonedInternalName :: Unique -> Name -> Name Source
mkSystemVarName :: Unique -> FastString -> Name Source
mkSysTvName :: Unique -> FastString -> Name Source
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 Name
s
nameUnique :: Name -> Unique Source
setNameUnique :: Name -> Unique -> Name Source
nameOccName :: Name -> OccName Source
nameModule :: Name -> Module Source
nameModule_maybe :: Name -> Maybe Module Source
setNameLoc :: Name -> SrcSpan -> Name Source
tidyNameOcc :: Name -> OccName -> Name Source
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
nameSrcLoc :: Name -> SrcLoc Source
nameSrcSpan :: Name -> SrcSpan Source
pprNameDefnLoc :: Name -> SDoc Source
pprDefinedAt :: Name -> SDoc Source
Predicates on Name
s
isSystemName :: Name -> Bool Source
isInternalName :: Name -> Bool Source
isExternalName :: Name -> Bool Source
isTyVarName :: Name -> Bool Source
isTyConName :: Name -> Bool Source
isDataConName :: Name -> Bool Source
isWiredInName :: Name -> Bool Source
isBuiltInSyntax :: Name -> 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 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
stableNameCmp :: Name -> Name -> Ordering Source
Class NamedThing
and overloaded friends
class NamedThing a where Source
A class allowing convenient access to the Name
of various datatypes
getSrcLoc :: NamedThing a => a -> SrcLoc Source
getSrcSpan :: NamedThing a => a -> SrcSpan Source
getOccString :: NamedThing a => a -> String Source
pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc Source
pprPrefixName :: (Outputable a, NamedThing a) => a -> SDoc Source
module OccName