ghc-7.0.1: The GHC API

RdrName

Contents

Description

GHC uses several kinds of name internally:

  • OccName.OccName: see OccName
  • RdrName is the type of names that come directly from the parser. They have not yet had their scoping and binding resolved by the renamer and can be thought of to a first approximation as an OccName.OccName with an optional module qualifier
  • Name: see Name
  • Id.Id: see Id
  • Var.Var: see Var

Synopsis

The main type

data RdrName Source

Do not use the data constructors of RdrName directly: prefer the family of functions that creates them, such as mkRdrUnqual

Constructors

Unqual OccName

Used for ordinary, unqualified occurrences, e.g. x, y or Foo. Create such a RdrName with mkRdrUnqual

Qual ModuleName OccName

A qualified name written by the user in source code. The module isn't necessarily the module where the thing is defined; just the one from which it is imported. Examples are Bar.x, Bar.y or Bar.Foo. Create such a RdrName with mkRdrQual

Orig Module OccName

An original name; the module is the defining module. This is used when GHC generates code that will be fed into the renamer (e.g. from deriving clauses), but where we want to say "Use Prelude.map dammit". One of these can be created with mkOrig

Exact Name

We know exactly the Name. This is used:

  1. When the parser parses built-in syntax like [] and (,), but wants a RdrName from it
  2. By Template Haskell, when TH has generated a unique name

Such a RdrName can be created by using getRdrName on a Name

Construction

mkQual :: NameSpace -> (FastString, FastString) -> RdrNameSource

Make a qualified RdrName in the given namespace and where the ModuleName and the OccName are taken from the first and second elements of the tuple respectively

getRdrName :: NamedThing thing => thing -> RdrNameSource

Destruction

setRdrNameSpace :: RdrName -> NameSpace -> RdrNameSource

This rather gruesome function is used mainly by the parser. When parsing:

 data T a = T | T1 Int

we parse the data constructors as types because of parser ambiguities, so then we need to change the type constr to a data constr

The exact-name case can occur when parsing:

 data [] a = [] | a : [a]

For the exact-name case we return an original name.

Printing

Local mapping of RdrName to Name

type LocalRdrEnv = OccEnv NameSource

This environment is used to store local bindings (let, where, lambda, case). It is keyed by OccName, because we never use it for qualified names

Global mapping of RdrName to GlobalRdrElts

type GlobalRdrEnv = OccEnv [GlobalRdrElt]Source

Keyed by OccName; when looking up a qualified name we look up the OccName part, and then check the Provenance to see if the appropriate qualification is valid. This saves routinely doubling the size of the env by adding both qualified and unqualified names to the domain.

The list in the codomain is required because there may be name clashes These only get reported on lookup, not on construction

INVARIANT: All the members of the list have distinct gre_name fields; that is, no duplicate Names

INVARIANT: Imported provenance => Name is an ExternalName However LocalDefs can have an InternalName. This happens only when type-checking a [d| ... |] Template Haskell quotation; see this note in RnNames Note [Top-level Names in Template Haskell decl quotes]

transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnvSource

Apply a transformation function to the GREs for these OccNames

findLocalDupsRdrEnv :: GlobalRdrEnv -> [OccName] -> (GlobalRdrEnv, [[Name]])Source

For each OccName, see if there are multiple local definitions for it. If so, remove all but one (to suppress subsequent error messages) and return a list of the duplicate bindings

pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]Source

Take a list of GREs which have the right OccName Pick those GREs that are suitable for this RdrName And for those, keep only only the Provenances that are suitable

Consider:

	 module A ( f ) where
	 import qualified Foo( f )
	 import Baz( f )
	 f = undefined

Let's suppose that Foo.f and Baz.f are the same entity really. The export of f is ambiguous because it's in scope from the local def and the import. The lookup of Unqual f should return a GRE for the locally-defined f, and a GRE for the imported f, with a single provenance, namely the one for Baz(f).

Global RdrName mapping elements: GlobalRdrElt, Provenance, ImportSpec

data GlobalRdrElt Source

An element of the GlobalRdrEnv

Constructors

GRE 

Fields

gre_name :: Name
 
gre_par :: Parent
 
gre_prov :: Provenance

Why it's in scope

unQualOK :: GlobalRdrElt -> BoolSource

Test if an unqualifed version of this thing would be in scope

qualSpecOK :: ModuleName -> ImportSpec -> BoolSource

Is in scope qualified with the given module?

unQualSpecOK :: ImportSpec -> BoolSource

Is in scope unqualified?

data Provenance Source

The Provenance of something says how it came to be in scope. It's quite elaborate so that we can give accurate unused-name warnings.

Constructors

LocalDef

The thing was defined locally

Imported [ImportSpec]

The thing was imported.

INVARIANT: the list of ImportSpec is non-empty

pprNameProvenance :: GlobalRdrElt -> SDocSource

Print out the place where the name was imported

data Parent Source

The children of a Name are the things that are abbreviated by the .. notation in export lists. Specifically: TyCon Children are * data constructors * record field ids Class Children are * class operations Each child has the parent thing as its Parent

Constructors

NoParent 
ParentIs Name 

data ImpDeclSpec Source

Describes a particular import declaration and is shared among all the Provenances for that decl

Constructors

ImpDeclSpec 

Fields

is_mod :: ModuleName

Module imported, e.g. import Muggle Note the Muggle may well not be the defining module for this thing!

is_as :: ModuleName

Import alias, e.g. from as M (or Muggle if there is no as clause)

is_qual :: Bool

Was this import qualified?

is_dloc :: SrcSpan

The location of the entire import declaration

data ImpItemSpec Source

Describes import info a particular Name

Constructors

ImpAll

The import had no import list, or had a hiding list

ImpSome

The import had an import list. The is_explicit field is True iff the thing was named explicitly in the import specs rather than being imported as part of a ... group. Consider:

 import C( T(..) )

Here the constructors of T are not named explicitly; only T is named explicitly.