diff options
Diffstat (limited to 'ghc/GHCi')
| -rw-r--r-- | ghc/GHCi/UI.hs | 10 | ||||
| -rw-r--r-- | ghc/GHCi/UI/Info.hs | 2 |
2 files changed, 6 insertions, 6 deletions
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 0da9741f30..3006af68c1 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -57,7 +57,7 @@ import GHC.Driver.Types ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_dynLinker, hsc_interp ) import GHC.Types.Module import GHC.Types.Name -import GHC.Driver.Packages ( unitIsTrusted, getPackageDetails, getInstalledPackageDetails, +import GHC.Driver.Packages ( unitIsTrusted, unsafeGetUnitInfo, getInstalledPackageDetails, listVisibleModuleNames, pprFlag ) import GHC.Iface.Syntax ( showToHeader ) import GHC.Core.Ppr.TyThing @@ -2340,8 +2340,8 @@ isSafeModule m = do mname = GHC.moduleNameString $ GHC.moduleName m packageTrusted dflags md - | thisPackage dflags == moduleUnitId md = True - | otherwise = unitIsTrusted $ getPackageDetails dflags (moduleUnitId md) + | thisPackage dflags == moduleUnit md = True + | otherwise = unitIsTrusted $ unsafeGetUnitInfo dflags (moduleUnit md) tallyPkgs dflags deps | not (packageTrustOn dflags) = (S.empty, S.empty) | otherwise = S.partition part deps @@ -4185,7 +4185,7 @@ lookupModuleName :: GHC.GhcMonad m => ModuleName -> m Module lookupModuleName mName = GHC.lookupModule mName Nothing isHomeModule :: Module -> Bool -isHomeModule m = GHC.moduleUnitId m == mainUnitId +isHomeModule m = GHC.moduleUnit m == mainUnitId -- TODO: won't work if home dir is encoded. -- (changeDirectory may not work either in that case.) @@ -4209,7 +4209,7 @@ wantInterpretedModuleName modname = do modl <- lookupModuleName modname let str = moduleNameString modname dflags <- getDynFlags - when (GHC.moduleUnitId modl /= thisPackage dflags) $ + when (GHC.moduleUnit modl /= thisPackage dflags) $ throwGhcException (CmdLineError ("module '" ++ str ++ "' is from another package;\nthis command requires an interpreted module")) is_interpreted <- GHC.moduleIsInterpreted modl when (not is_interpreted) $ diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs index 22eb664856..9751aceb8b 100644 --- a/ghc/GHCi/UI/Info.hs +++ b/ghc/GHCi/UI/Info.hs @@ -190,7 +190,7 @@ resolveNameFromModule infos name = do modL <- maybe (throwE $ "No module for" <+> ppr name) return $ nameModule_maybe name - info <- maybe (throwE (ppr (moduleUnitId modL) <> ":" <> + info <- maybe (throwE (ppr (moduleUnit modL) <> ":" <> ppr modL)) return $ M.lookup (moduleName modL) infos |
