| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Types.Name
Description
GHC uses several kinds of name internally:
- OccName: see GHC.Types.Name.Occurrence
- RdrName: see GHC.Types.Name.Reader
- Nameis the type of names that have had their scoping and binding resolved. They have an- OccNamebut also a- Uniquethat disambiguates Names that have the same- OccNameand indeed is used for all- Namecomparison. Names also contain information about where they originated from, see GHC.Types.Name
- Id: see GHC.Types.Id
- Var: see GHC.Types.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
Synopsis
- 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 -> FastString -> Name
- mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
- mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name
- nameUnique :: Name -> Unique
- setNameUnique :: Name -> Unique -> Name
- nameOccName :: Name -> OccName
- nameNameSpace :: Name -> NameSpace
- nameModule :: HasDebugCallStack => Name -> Module
- nameModule_maybe :: Name -> Maybe Module
- setNameLoc :: Name -> SrcSpan -> Name
- tidyNameOcc :: Name -> OccName -> Name
- localiseName :: Name -> Name
- namePun_maybe :: Name -> Maybe FastString
- pprName :: forall doc. IsLine doc => Name -> doc
- nameSrcLoc :: Name -> SrcLoc
- nameSrcSpan :: Name -> SrcSpan
- pprNameDefnLoc :: Name -> SDoc
- pprDefinedAt :: Name -> SDoc
- pprFullName :: Module -> Name -> SDoc
- pprTickyName :: Module -> 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
- isDynLinkName :: Platform -> Module -> Name -> Bool
- isWiredInName :: Name -> Bool
- isWiredIn :: NamedThing thing => thing -> Bool
- isBuiltInSyntax :: Name -> Bool
- isHoleName :: Name -> Bool
- wiredInNameTyThing_maybe :: Name -> Maybe TyThing
- nameIsLocalOrFrom :: Module -> Name -> Bool
- nameIsExternalOrFrom :: Module -> Name -> Bool
- nameIsHomePackage :: Module -> Name -> Bool
- nameIsHomePackageImport :: Module -> Name -> Bool
- nameIsFromExternalPackage :: HomeUnit -> 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
- getOccFS :: NamedThing a => a -> FastString
- pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc
- pprPrefixName :: NamedThing a => a -> SDoc
- pprModulePrefix :: IsLine doc => PprStyle -> Module -> OccName -> doc
- pprNameUnqualified :: Name -> SDoc
- nameStableString :: Name -> String
- module GHC.Types.Name.Occurrence
The main types
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
| Data Name Source # | |
| 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 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # 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 :: forall r r'. (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 # | |
| NFData Name Source # | |
| Defined in GHC.Types.Name | |
| NamedThing Name Source # | |
| HasOccName Name Source # | |
| Uniquable Name Source # | |
| Binary Name Source # | Assumes that the  | 
| Outputable Name Source # | |
| OutputableBndr Name Source # | |
| Defined in GHC.Types.Name | |
| Eq Name Source # | |
| Ord Name Source # | Caution: This instance is implemented via  See  | 
| type Anno Name Source # | |
| Defined in GHC.Hs.Extension | |
| type Anno (LocatedN Name) Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno [LocatedN Name] Source # | |
| Defined in GHC.Hs.Binds | |
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
mkSystemVarName :: Unique -> FastString -> Name Source #
mkSysTvName :: Unique -> FastString -> Name Source #
mkFCallName :: Unique -> FastString -> 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
nameUnique :: Name -> Unique Source #
nameOccName :: Name -> OccName Source #
nameNameSpace :: Name -> NameSpace Source #
nameModule :: HasDebugCallStack => Name -> Module Source #
localiseName :: Name -> Name Source #
Make the Name into an internal name, regardless of what it was to begin with
namePun_maybe :: Name -> Maybe FastString Source #
nameSrcLoc :: Name -> SrcLoc Source #
nameSrcSpan :: Name -> SrcSpan Source #
pprNameDefnLoc :: Name -> SDoc Source #
pprDefinedAt :: Name -> SDoc Source #
pprFullName :: Module -> Name -> SDoc Source #
Print fully qualified name (with unit-id, module and unique)
pprTickyName :: Module -> Name -> SDoc Source #
Print a ticky ticky styled name
Module argument is the module to use for internal and system names. When printing the name in a ticky profile, the module name is included even for local things. However, ticky uses the format "x (M)" rather than "M.x". Hence, this function provides a separation from normal styling.
Predicates on Names
isSystemName :: Name -> Bool Source #
isInternalName :: Name -> Bool Source #
isExternalName :: Name -> Bool Source #
isTyVarName :: Name -> Bool Source #
isTyConName :: Name -> Bool Source #
isDataConName :: Name -> Bool Source #
isDynLinkName :: Platform -> Module -> Name -> Bool Source #
Will the Name come from a dynamically linked package?
isWiredInName :: Name -> Bool Source #
isWiredIn :: NamedThing thing => thing -> Bool Source #
isBuiltInSyntax :: Name -> Bool Source #
isHoleName :: 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 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.Runtime.Context
nameIsExternalOrFrom :: Module -> Name -> Bool Source #
Returns True if the name is external or from the interactive package
 See documentation of nameIsLocalOrFrom function
nameIsFromExternalPackage :: HomeUnit -> 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
Instances
| NamedThing Class Source # | |
| NamedThing ConLike Source # | |
| NamedThing DataCon Source # | |
| NamedThing FamInst Source # | |
| NamedThing ClsInst Source # | |
| NamedThing PatSyn Source # | |
| NamedThing TyCon Source # | |
| NamedThing IfaceClassOp Source # | |
| Defined in GHC.Iface.Syntax | |
| NamedThing IfaceConDecl Source # | |
| Defined in GHC.Iface.Syntax | |
| NamedThing IfaceDecl Source # | |
| NamedThing HoleFitCandidate Source # | |
| Defined in GHC.Tc.Errors.Hole.FitTypes Methods getOccName :: HoleFitCandidate -> OccName Source # getName :: HoleFitCandidate -> Name Source # | |
| NamedThing Name Source # | |
| NamedThing TyThing Source # | |
| NamedThing Var Source # | |
| NamedThing (CoAxiom br) Source # | |
| NamedThing e => NamedThing (Located e) Source # | |
| NamedThing (Located a) => NamedThing (LocatedAn an a) Source # | |
| NamedThing tv => NamedThing (VarBndr tv flag) Source # | |
| NamedThing (HsTyVarBndr flag GhcRn) Source # | |
| Defined in GHC.Hs.Type Methods getOccName :: HsTyVarBndr flag GhcRn -> OccName Source # | |
getSrcLoc :: NamedThing a => a -> SrcLoc Source #
getSrcSpan :: NamedThing a => a -> SrcSpan Source #
getOccString :: NamedThing a => a -> String Source #
getOccFS :: NamedThing a => a -> FastString Source #
pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc Source #
pprPrefixName :: NamedThing a => a -> SDoc 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"
module GHC.Types.Name.Occurrence