ghc-7.8.20140130: The GHC API

Safe HaskellNone
LanguageHaskell98

Name

Contents

Description

GHC uses several kinds of name internally:

  • OccName: see "OccName#name_types"
  • RdrName: see "RdrName#name_types"
  • 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#name_sorts"
  • Id: see "Id#name_types"
  • Var: see "Var#name_types"

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 NameSource

A unique, unambigious name for something, containing information about where that thing originated.

data BuiltInSyntaxSource

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 -> NameSource

Create a name brought into being by the compiler

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

mkFCallName :: Unique -> String -> NameSource

Make a name for a foreign call

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

localiseName :: Name -> NameSource

Make the Name into an internal name, regardless of what it was to begin with

mkLocalisedOccName :: Module -> (Maybe String -> OccName -> OccName) -> Name -> OccNameSource

Create a localised variant of a name.

If the name is external, encode the original's module name to disambiguate.

Predicates on Names

Class NamedThing and overloaded friends

module OccName