ghc-8.0.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

RdrName

Contents

Description

GHC uses several kinds of name internally:

  • 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 with an optional module qualifier
  • Name: see Name
  • Id: see Id
  • 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

  • Note: A Located RdrName will only have API Annotations if it is a compound one, e.g.
`bar`
( ~ )

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

Instances

Eq RdrName # 

Methods

(==) :: RdrName -> RdrName -> Bool #

(/=) :: RdrName -> RdrName -> Bool #

Data RdrName # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName Source #

toConstr :: RdrName -> Constr Source #

dataTypeOf :: RdrName -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) Source #

gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source #

Ord RdrName # 
OutputableBndr RdrName # 
Outputable RdrName # 
HasOccName RdrName # 
type PostRn RdrName ty # 
type PostTc RdrName ty # 

Construction

mkQual :: NameSpace -> (FastString, FastString) -> RdrName Source #

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 -> RdrName Source #

Destruction

Local mapping of RdrName to Name

data LocalRdrEnv Source #

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 We keep the current mapping, *and* the set of all Names in scope Reason: see Note [Splicing Exact names] in RnEnv The field lre_nwcs is used to keep names of type variables that should be replaced with named wildcards. See Note [Renaming named wild cards] in RnTypes

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 1: All the members of the list have distinct gre_name fields; that is, no duplicate Names

INVARIANT 2: 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 -> GlobalRdrEnv Source #

Apply a transformation function to the GREs for these OccNames

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

Takes a list of GREs which have the right OccName x Pick those GREs that are are in scope * Qualified, as x if want_qual is Qual M _ * Unqualified, as x if want_unqual is Unqual _

Return each such GRE, with its ImportSpecs filtered, to reflect how it is in scope qualifed or unqualified respectively. See Note [GRE filtering]

pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)] Source #

Pick GREs that are in scope *both* qualified *and* unqualified Return each GRE that is, as a pair (qual_gre, unqual_gre) These two GREs are the original GRE with imports filtered to express how it is in scope qualified an unqualified respectively

Used only for the 'module M' item in export list; see RnNames.exports_from_avail

GlobalRdrElts

gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt] Source #

make a GlobalRdrEnv where all the elements point to the same Provenance (useful for "hiding" imports, or imports with no details).

Global RdrName mapping elements: GlobalRdrElt, Provenance, ImportSpec

data GlobalRdrElt Source #

An element of the GlobalRdrEnv

Constructors

GRE 

Fields

Instances

Data GlobalRdrElt # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalRdrElt Source #

toConstr :: GlobalRdrElt -> Constr Source #

dataTypeOf :: GlobalRdrElt -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalRdrElt) Source #

gmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrElt -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt Source #

Outputable GlobalRdrElt # 

unQualOK :: GlobalRdrElt -> Bool Source #

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

qualSpecOK :: ModuleName -> ImportSpec -> Bool Source #

Is in scope qualified with the given module?

unQualSpecOK :: ImportSpec -> Bool Source #

Is in scope unqualified?

pprNameProvenance :: GlobalRdrElt -> SDoc Source #

Print out one place where the name was define/imported (With -dppr-debug, print them all)

data Parent Source #

The children of a Name are the things that are abbreviated by the ".." notation in export lists. See Note [Parents]

Constructors

NoParent 
ParentIs 

Fields

FldParent

See Note [Parents for record fields]

PatternSynonym 

Instances

Eq Parent # 

Methods

(==) :: Parent -> Parent -> Bool #

(/=) :: Parent -> Parent -> Bool #

Data Parent # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parent -> c Parent Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parent Source #

toConstr :: Parent -> Constr Source #

dataTypeOf :: Parent -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Parent) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent) Source #

gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Parent -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parent -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parent -> m Parent Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent Source #

Outputable Parent # 

data ImportSpec Source #

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

Constructors

ImpSpec 

Instances

Eq ImportSpec # 
Data ImportSpec # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSpec -> c ImportSpec Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec Source #

toConstr :: ImportSpec -> Constr Source #

dataTypeOf :: ImportSpec -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec Source #

Ord ImportSpec # 
Outputable ImportSpec # 

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

Instances

Eq ImpDeclSpec # 
Data ImpDeclSpec # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpDeclSpec Source #

toConstr :: ImpDeclSpec -> Constr Source #

dataTypeOf :: ImpDeclSpec -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpDeclSpec) Source #

gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec Source #

Ord ImpDeclSpec # 

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.

Instances

Eq ImpItemSpec # 
Data ImpItemSpec # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpItemSpec Source #

toConstr :: ImpItemSpec -> Constr Source #

dataTypeOf :: ImpItemSpec -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpItemSpec) Source #

gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImpItemSpec -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec Source #

Ord ImpItemSpec #