ghc-6.12.2: The GHC APISource codeContentsIndex
Name
Contents
The main types
Creating Names
Manipulating and deconstructing Names
Predicates on Names
Class NamedThing and overloaded friends
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
data Name
data BuiltInSyntax
= BuiltInSyntax
| UserSyntax
mkInternalName :: Unique -> OccName -> SrcSpan -> Name
mkSystemName :: Unique -> OccName -> Name
mkSystemVarName :: Unique -> FastString -> Name
mkSysTvName :: Unique -> FastString -> Name
mkFCallName :: Unique -> String -> Name
mkIPName :: Unique -> OccName -> Name
mkTickBoxOpName :: 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
tidyNameOcc :: Name -> OccName -> Name
hashName :: Name -> Int
localiseName :: Name -> Name
nameSrcLoc :: Name -> SrcLoc
nameSrcSpan :: Name -> SrcSpan
pprNameLoc :: 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
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
data Name Source
A unique, unambigious name for something, containing information about where that thing originated.
show/hide Instances
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
mkInternalName :: Unique -> OccName -> SrcSpan -> NameSource
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 -> NameSource
Create a name brought into being by the compiler
mkSystemVarName :: Unique -> FastString -> NameSource
mkSysTvName :: Unique -> FastString -> NameSource
mkFCallName :: Unique -> String -> NameSource
Make a name for a foreign call
mkIPName :: Unique -> OccName -> NameSource
Make the name of an implicit parameter
mkTickBoxOpName :: Unique -> String -> NameSource
mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> NameSource
Create a name which definitely originates in the given module
mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> NameSource
Create a name which is actually defined by the compiler itself
Manipulating and deconstructing Names
nameUnique :: Name -> UniqueSource
setNameUnique :: Name -> Unique -> NameSource
nameOccName :: Name -> OccNameSource
nameModule :: Name -> ModuleSource
nameModule_maybe :: Name -> Maybe ModuleSource
tidyNameOcc :: Name -> OccName -> NameSource
hashName :: Name -> IntSource
localiseName :: Name -> NameSource
Make the Name into an internal name, regardless of what it was to begin with
nameSrcLoc :: Name -> SrcLocSource
nameSrcSpan :: Name -> SrcSpanSource
pprNameLoc :: Name -> SDocSource
Predicates on Names
isSystemName :: Name -> BoolSource
isInternalName :: Name -> BoolSource
isExternalName :: Name -> BoolSource
isTyVarName :: Name -> BoolSource
isTyConName :: Name -> BoolSource
isDataConName :: Name -> BoolSource
isValName :: Name -> BoolSource
isVarName :: Name -> BoolSource
isWiredInName :: Name -> BoolSource
isBuiltInSyntax :: Name -> BoolSource
wiredInNameTyThing_maybe :: Name -> Maybe TyThingSource
nameIsLocalOrFrom :: Module -> Name -> BoolSource
Class NamedThing and overloaded friends
class NamedThing a whereSource
A class allowing convenient access to the Name of various datatypes
Methods
getOccName :: a -> OccNameSource
getName :: a -> NameSource
show/hide Instances
getSrcLoc :: NamedThing a => a -> SrcLocSource
getSrcSpan :: NamedThing a => a -> SrcSpanSource
getOccString :: NamedThing a => a -> StringSource
pprInfixName :: (Outputable a, NamedThing a) => a -> SDocSource
pprPrefixName :: (Outputable a, NamedThing a) => a -> SDocSource
pprModulePrefix :: PprStyle -> Module -> OccName -> SDocSource
module OccName
Produced by Haddock version 2.6.1