ghc-lib-9.8.2.20240223: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Rename.Env

Synopsis

Documentation

lookupInfoOccRn :: RdrName -> RnM [Name] Source #

lookupInfoOccRn is intended for use in GHCi's ":info" command It finds all the GREs that RdrName could mean, not complaining about ambiguity, but rather returning them all (c.f. #9881).

lookupInfoOccRn is also used in situations where we check for at least one definition of the RdrName, not complaining about multiple definitions (see #17832).

lookupExprOccRn :: RdrName -> RnM (Maybe GlobalRdrElt) 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).

If -XDisambiguateRecordFields is off, then we will pass Nothing for the DataCon Name, i.e. we don't use the data constructor for disambiguation. See Note [DisambiguateRecordFields] and Note [NoFieldSelectors].

lookupRecUpdFields :: NonEmpty (LHsRecUpdField GhcPs GhcPs) -> RnM (NonEmpty (HsRecUpdParent GhcRn)) Source #

Returns all possible collections of field labels for the given record update.

Example:

data D = MkD { fld1 :: Int, fld2 :: Bool } data E = MkE1 { fld1 :: Int, fld2 :: Bool, fld3 :: Char } | MkE2 { fld1 :: Int, fld2 :: Bool } data F = MkF1 { fld1 :: Int } | MkF2 { fld2 :: Bool }

f r = r { fld1 = a, fld2 = b }

This function will return:

[ D.fld1, D.fld2
-- could be a record update at type D , [ E.fld1, E.fld2 ] -- could be a record update at type E ] -- cannot be a record update at type F: no constructor has both -- of the fields fld1 and fld2

If there are no valid parents for the record update, throws a TcRnBadRecordUpdate error.

getUpdFieldLbls :: forall p q. UnXRec (GhcPass p) => [LHsRecUpdField (GhcPass p) q] -> [RdrName] Source #

data ChildLookupResult Source #

Constructors

NameNotFound

We couldn't find a suitable name

IncorrectParent

The child has an incorrect parent

Fields

  • Name

    parent

  • GlobalRdrElt

    child we were looking for

  • [Name]

    list of possible parents | We resolved to a child

FoundChild GlobalRdrElt 

Instances

Instances details
Outputable ChildLookupResult Source # 
Instance details

Defined in GHC.Rename.Env

lookupSubBndrOcc_helper Source #

Arguments

:: Bool 
-> DeprecationWarnings 
-> Name 
-> RdrName

thing we are looking up

-> LookupChild

how to look it up (e.g. which NameSpaces to look in)

-> RnM ChildLookupResult 

Used in export lists to lookup the children.

lookupSigCtxtOccRn Source #

Arguments

:: HsSigCtxt 
-> SDoc

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

-> GenLocated (SrcSpanAnn' ann) RdrName 
-> RnM (GenLocated (SrcSpanAnn' ann) Name) 

Lookup a name in relation to the names in a HsSigCtxt

lookupConstructorInfo :: HasDebugCallStack => Name -> RnM ConInfo Source #

Look up the arity and record fields of a constructor.

lookupGREInfo :: HasDebugCallStack => HscEnv -> Name -> GREInfo Source #

Look up the GREInfo associated with the given Name by looking up in the type environment.

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

data DeprecationWarnings Source #

Whether to report deprecation warnings when registering a used GRE

There is no option to only emit declaration warnings since everywhere we emit the declaration warnings we also emit export warnings (See Note [Handling of deprecations] for details)