Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newTopSrcBinder :: LocatedN RdrName -> RnM Name
- lookupLocatedTopBndrRn :: Located RdrName -> RnM (Located Name)
- lookupLocatedTopBndrRnN :: LocatedN RdrName -> RnM (LocatedN Name)
- lookupTopBndrRn :: RdrName -> RnM Name
- lookupLocatedOccRn :: GenLocated (SrcSpanAnn' ann) RdrName -> TcRn (GenLocated (SrcSpanAnn' ann) Name)
- lookupOccRn :: RdrName -> RnM Name
- lookupOccRn_maybe :: RdrName -> RnM (Maybe Name)
- lookupLocalOccRn_maybe :: RdrName -> RnM (Maybe Name)
- lookupInfoOccRn :: RdrName -> RnM [Name]
- lookupLocalOccThLvl_maybe :: Name -> RnM (Maybe (TopLevelFlag, ThLevel))
- lookupLocalOccRn :: RdrName -> RnM Name
- lookupTypeOccRn :: RdrName -> RnM Name
- lookupGlobalOccRn :: RdrName -> RnM Name
- lookupGlobalOccRn_maybe :: RdrName -> RnM (Maybe Name)
- data AmbiguousResult
- lookupExprOccRn :: DuplicateRecordFields -> RdrName -> RnM (Maybe AmbiguousResult)
- lookupRecFieldOcc :: Maybe Name -> RdrName -> RnM Name
- lookupRecFieldOcc_update :: DuplicateRecordFields -> RdrName -> RnM AmbiguousResult
- data ChildLookupResult
- lookupSubBndrOcc_helper :: Bool -> Bool -> Name -> RdrName -> RnM ChildLookupResult
- combineChildLookupResult :: [RnM ChildLookupResult] -> RnM ChildLookupResult
- data HsSigCtxt
- lookupLocalTcNames :: HsSigCtxt -> SDoc -> RdrName -> RnM [(RdrName, Name)]
- lookupSigOccRn :: HsSigCtxt -> Sig GhcPs -> LocatedA RdrName -> RnM (LocatedA Name)
- lookupSigOccRnN :: HsSigCtxt -> Sig GhcPs -> LocatedN RdrName -> RnM (LocatedN Name)
- lookupSigCtxtOccRn :: HsSigCtxt -> SDoc -> LocatedA RdrName -> RnM (LocatedA Name)
- lookupSigCtxtOccRnN :: HsSigCtxt -> SDoc -> LocatedN RdrName -> RnM (LocatedN Name)
- lookupInstDeclBndr :: Name -> SDoc -> RdrName -> RnM Name
- lookupFamInstName :: Maybe Name -> LocatedN RdrName -> RnM (LocatedN Name)
- lookupConstructorFields :: Name -> RnM [FieldLabel]
- lookupGreAvailRn :: RdrName -> RnM (Name, AvailInfo)
- lookupSyntax :: Name -> RnM (SyntaxExpr GhcRn, FreeVars)
- lookupSyntaxExpr :: Name -> RnM (HsExpr GhcRn, FreeVars)
- lookupSyntaxNames :: [Name] -> RnM ([HsExpr GhcRn], FreeVars)
- lookupSyntaxName :: Name -> RnM (Name, FreeVars)
- lookupIfThenElse :: RnM (Maybe Name)
- lookupQualifiedDoExpr :: HsStmtContext p -> Name -> RnM (HsExpr GhcRn, FreeVars)
- lookupQualifiedDo :: HsStmtContext p -> Name -> RnM (SyntaxExpr GhcRn, FreeVars)
- lookupQualifiedDoName :: HsStmtContext p -> Name -> RnM (Name, FreeVars)
- lookupNameWithQualifier :: Name -> ModuleName -> RnM (Name, FreeVars)
- addUsedGRE :: Bool -> GlobalRdrElt -> RnM ()
- addUsedGREs :: [GlobalRdrElt] -> RnM ()
- addUsedDataCons :: GlobalRdrEnv -> TyCon -> RnM ()
- dataTcOccs :: RdrName -> [RdrName]
Documentation
lookupLocatedOccRn :: GenLocated (SrcSpanAnn' ann) RdrName -> TcRn (GenLocated (SrcSpanAnn' ann) Name) Source #
lookupLocalOccThLvl_maybe :: Name -> RnM (Maybe (TopLevelFlag, ThLevel)) Source #
data AmbiguousResult Source #
Result of looking up an occurrence that might be an ambiguous field.
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 :: DuplicateRecordFields -> RdrName -> RnM (Maybe AmbiguousResult) 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]). The
DuplicateRecordFields
argument controls whether ambiguous fields will be
allowed (resulting in an AmbiguousFields
result being returned).
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]).
data ChildLookupResult Source #
Instances
Outputable ChildLookupResult Source # | |
Defined in GHC.Rename.Env ppr :: ChildLookupResult -> SDoc Source # |
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
TopSigCtxt NameSet | |
LocalBindCtxt NameSet | |
ClsDeclCtxt Name | |
InstDeclCtxt NameSet | |
HsBootCtxt NameSet | |
RoleAnnotCtxt NameSet |
Instances
:: 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
:: 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
lookupConstructorFields :: Name -> RnM [FieldLabel] Source #
lookupSyntax :: Name -> RnM (SyntaxExpr GhcRn, FreeVars) Source #
:: Name | The standard name |
-> RnM (Name, FreeVars) | Possibly a non-standard name Lookup a Name that may be subject to Rebindable Syntax (RS).
|
lookupQualifiedDoExpr :: HsStmtContext p -> Name -> RnM (HsExpr GhcRn, FreeVars) Source #
lookupQualifiedDo :: HsStmtContext p -> Name -> RnM (SyntaxExpr GhcRn, FreeVars) Source #
lookupQualifiedDoName :: HsStmtContext p -> Name -> RnM (Name, FreeVars) Source #
lookupNameWithQualifier :: Name -> ModuleName -> RnM (Name, FreeVars) Source #
addUsedGRE :: Bool -> GlobalRdrElt -> RnM () Source #
addUsedGREs :: [GlobalRdrElt] -> RnM () Source #
addUsedDataCons :: GlobalRdrEnv -> TyCon -> RnM () Source #
dataTcOccs :: RdrName -> [RdrName] Source #