ghc-9.6.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Rename.Env

Synopsis

Documentation

data AmbiguousResult Source #

Result of looking up an occurrence that might be an ambiguous field.

Constructors

UnambiguousGre GreName

Occurrence picked out a single name, which may or may not belong to a field (or might be unbound, if an error has been reported already, per Note [ Unbound vs Ambiguous Names ]).

AmbiguousFields

Occurrence picked out two or more fields, and no non-fields. For now this is allowed by DuplicateRecordFields in certain circumstances, as the type-checker may be able to disambiguate later.

lookupExprOccRn :: RdrName -> RnM (Maybe GreName) Source #

Look up a RdrName used as a variable in an expression.

This may be a local variable, global variable, or one or more record selector functions. It will not return record fields created with the NoFieldSelectors extension (see Note [NoFieldSelectors]).

If the name is not in scope at the term level, but its promoted equivalent is in scope at the type level, the lookup will succeed (so that the type-checker can report a more informative error later). See Note [Promotion].

lookupRecFieldOcc :: Maybe Name -> RdrName -> RnM Name Source #

Look up an occurrence of a field in record construction or pattern matching (but not update). When the -XDisambiguateRecordFields flag is on, take account of the data constructor name to disambiguate which field to use.

See Note [DisambiguateRecordFields] and Note [NoFieldSelectors].

lookupRecFieldOcc_update :: DuplicateRecordFields -> RdrName -> RnM AmbiguousResult Source #

Look up an occurrence of a field in a record update, returning the selector name.

Unlike construction and pattern matching with -XDisambiguateRecordFields (see lookupRecFieldOcc), there is no data constructor to help disambiguate, so this may be ambiguous if the field is in scope multiple times. However we ignore non-fields in scope with the same name if -XDisambiguateRecordFields is on (see Note [DisambiguateRecordFields for updates]).

Here a field is in scope even if NoFieldSelectors was enabled at its definition site (see Note [NoFieldSelectors]).

lookupSubBndrOcc_helper :: Bool -> Bool -> Name -> RdrName -> RnM ChildLookupResult Source #

Used in export lists to lookup the children.

combineChildLookupResult :: [RnM ChildLookupResult] -> RnM ChildLookupResult Source #

Specialised version of msum for RnM ChildLookupResult

lookupSigCtxtOccRn Source #

Arguments

:: HsSigCtxt 
-> SDoc

description of thing we're looking up, like "type family"

-> LocatedA RdrName 
-> RnM (LocatedA Name) 

Lookup a name in relation to the names in a HsSigCtxt

lookupSigCtxtOccRnN Source #

Arguments

:: HsSigCtxt 
-> SDoc

description of thing we're looking up, like "type family"

-> LocatedN RdrName 
-> RnM (LocatedN Name) 

Lookup a name in relation to the names in a HsSigCtxt

lookupSyntaxExpr Source #

Arguments

:: Name

The standard name

-> RnM (HsExpr GhcRn, FreeVars)

Possibly a non-standard name

lookupSyntaxName Source #

Arguments

:: Name

The standard name

-> RnM (Name, FreeVars)

Possibly a non-standard name Lookup a Name that may be subject to Rebindable Syntax (RS).

  • When RS is off, just return the supplied (standard) Name
  • When RS is on, look up the OccName of the supplied Name; return what we find, or the supplied Name if there is nothing in scope