|
|
|
|
|
Description |
GHC uses several kinds of name internally:
- OccName: see OccName
- RdrName.RdrName: see RdrName
- Name is the type of names that have had their scoping and binding resolved. They
have an OccName but also a Unique that disambiguates Names that have
the same OccName and indeed is used for all Name comparison. Names
also contain information about where they originated from, see Name
- Id.Id: see Id
- Var.Var: see Var
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 |
A unique, unambigious name for something, containing information about where
that thing originated.
| Instances | |
|
|
data BuiltInSyntax |
BuiltInSyntax is for things like (:), [] and tuples,
which have special syntactic forms. They aren't in scope
as such.
| Constructors | |
|
|
Creating Names
|
|
mkInternalName :: Unique -> OccName -> SrcSpan -> Name |
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
|
|
mkSystemName :: Unique -> OccName -> Name |
Create a name brought into being by the compiler
|
|
mkSystemVarName :: Unique -> FastString -> Name |
|
mkSysTvName :: Unique -> FastString -> Name |
|
mkFCallName :: Unique -> String -> Name |
Make a name for a foreign call
|
|
mkIPName :: Unique -> OccName -> Name |
Make the name of an implicit parameter
|
|
mkTickBoxOpName :: Unique -> String -> Name |
|
mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name |
Create a name which definitely originates in the given module
|
|
mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name |
Create a name which is actually defined by the compiler itself
|
|
Manipulating and deconstructing Names
|
|
nameUnique :: Name -> Unique |
|
setNameUnique :: Name -> Unique -> Name |
|
nameOccName :: Name -> OccName |
|
nameModule :: Name -> Module |
|
nameModule_maybe :: Name -> Maybe Module |
|
tidyNameOcc :: Name -> OccName -> Name |
|
hashName :: Name -> Int |
|
localiseName :: Name -> Name |
Make the Name into an internal name, regardless of what it was to begin with
|
|
nameSrcLoc :: Name -> SrcLoc |
|
nameSrcSpan :: Name -> SrcSpan |
|
pprNameLoc :: Name -> SDoc |
|
Predicates on Names
|
|
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 |
|
Class NamedThing and overloaded friends
|
|
class NamedThing a where |
A class allowing convenient access to the Name of various datatypes
| | Methods | | | Instances | |
|
|
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 |
|
module OccName |
|
Produced by Haddock version 2.4.2 |