ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Rename.Names

Synopsis

Documentation

rnImports :: [LImportDecl GhcPs] -> RnM ([LImportDecl GhcRn], GlobalRdrEnv, ImportAvails, AnyHpcUsage) Source #

Process Import Decls. See rnImportDecl for a description of what the return types represent. Note: Do the non SOURCE ones first, so that we get a helpful warning for SOURCE ones that are unnecessary

getLocalNonValBinders :: MiniFixityEnv -> HsGroup GhcPs -> RnM ((TcGblEnv, TcLclEnv), NameSet) Source #

newRecordSelector :: Bool -> [Name] -> LFieldOcc GhcPs -> RnM FieldLabel Source #

extendGlobalRdrEnvRn :: [AvailInfo] -> MiniFixityEnv -> RnM (TcGblEnv, TcLclEnv) Source #

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

calculateAvails :: HomeUnit -> ModIface -> IsSafeImport -> IsBootInterface -> ImportedBy -> ImportAvails Source #

Calculate the ImportAvails induced by an import of a particular interface, but without imp_mods.

reportUnusedNames :: TcGblEnv -> HscSource -> RnM () Source #

mkChildEnv :: [GlobalRdrElt] -> NameEnv [GlobalRdrElt] Source #

findChildren :: NameEnv [a] -> Name -> [a] Source #

dodgyMsg :: (Outputable a, Outputable b) => SDoc -> a -> b -> SDoc Source #

dodgyMsgInsert :: forall p. IdP (GhcPass p) -> IE (GhcPass p) Source #

findImportUsage :: [LImportDecl GhcRn] -> [GlobalRdrElt] -> [ImportDeclUsage] Source #

getMinimalImports :: [ImportDeclUsage] -> RnM [LImportDecl GhcRn] Source #

printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM () Source #

type ImportDeclUsage = (LImportDecl GhcRn, [GlobalRdrElt], [Name]) Source #