{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
module GHC.Driver.Finder (
flushFinderCaches,
FindResult(..),
findImportedModule,
findPluginModule,
findExactModule,
findHomeModule,
findExposedPackageModule,
mkHomeModLocation,
mkHomeModLocation2,
mkHiOnlyModLocation,
mkHiPath,
mkObjPath,
addHomeModuleToFinder,
uncacheModule,
mkStubPaths,
findObjectLinkableMaybe,
findObjectLinkable,
cannotFindModule,
cannotFindInterface,
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Unit
import GHC.Driver.Types
import GHC.Data.FastString
import GHC.Utils.Misc
import GHC.Builtin.Names ( gHC_PRIM )
import GHC.Driver.Session
import GHC.Driver.Ways
import GHC.Utils.Outputable as Outputable
import GHC.Data.Maybe ( expectJust )
import Data.IORef ( IORef, readIORef, atomicModifyIORef' )
import System.Directory
import System.FilePath
import Control.Monad
import Data.Time
type FileExt = String
type BaseName = String
flushFinderCaches :: HscEnv -> IO ()
flushFinderCaches :: HscEnv -> IO ()
flushFinderCaches HscEnv
hsc_env =
IORef FinderCache -> (FinderCache -> (FinderCache, ())) -> IO ()
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FinderCache
fc_ref ((FinderCache -> (FinderCache, ())) -> IO ())
-> (FinderCache -> (FinderCache, ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FinderCache
fm -> ((InstalledModule -> InstalledFindResult -> Bool)
-> FinderCache -> FinderCache
forall a.
(InstalledModule -> a -> Bool)
-> InstalledModuleEnv a -> InstalledModuleEnv a
filterInstalledModuleEnv InstalledModule -> InstalledFindResult -> Bool
forall {p}. InstalledModule -> p -> Bool
is_ext FinderCache
fm, ())
where
this_pkg :: Unit
this_pkg = DynFlags -> Unit
homeUnit (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
fc_ref :: IORef FinderCache
fc_ref = HscEnv -> IORef FinderCache
hsc_FC HscEnv
hsc_env
is_ext :: InstalledModule -> p -> Bool
is_ext InstalledModule
mod p
_ | Bool -> Bool
not (InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit InstalledModule
mod UnitId -> Unit -> Bool
`unitIdEq` Unit
this_pkg) = Bool
True
| Bool
otherwise = Bool
False
addToFinderCache :: IORef FinderCache -> InstalledModule -> InstalledFindResult -> IO ()
addToFinderCache :: IORef FinderCache
-> InstalledModule -> InstalledFindResult -> IO ()
addToFinderCache IORef FinderCache
ref InstalledModule
key InstalledFindResult
val =
IORef FinderCache -> (FinderCache -> (FinderCache, ())) -> IO ()
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FinderCache
ref ((FinderCache -> (FinderCache, ())) -> IO ())
-> (FinderCache -> (FinderCache, ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FinderCache
c -> (FinderCache
-> InstalledModule -> InstalledFindResult -> FinderCache
forall a.
InstalledModuleEnv a
-> InstalledModule -> a -> InstalledModuleEnv a
extendInstalledModuleEnv FinderCache
c InstalledModule
key InstalledFindResult
val, ())
removeFromFinderCache :: IORef FinderCache -> InstalledModule -> IO ()
removeFromFinderCache :: IORef FinderCache -> InstalledModule -> IO ()
removeFromFinderCache IORef FinderCache
ref InstalledModule
key =
IORef FinderCache -> (FinderCache -> (FinderCache, ())) -> IO ()
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FinderCache
ref ((FinderCache -> (FinderCache, ())) -> IO ())
-> (FinderCache -> (FinderCache, ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FinderCache
c -> (FinderCache -> InstalledModule -> FinderCache
forall a.
InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
delInstalledModuleEnv FinderCache
c InstalledModule
key, ())
lookupFinderCache :: IORef FinderCache -> InstalledModule -> IO (Maybe InstalledFindResult)
lookupFinderCache :: IORef FinderCache
-> InstalledModule -> IO (Maybe InstalledFindResult)
lookupFinderCache IORef FinderCache
ref InstalledModule
key = do
FinderCache
c <- IORef FinderCache -> IO FinderCache
forall a. IORef a -> IO a
readIORef IORef FinderCache
ref
Maybe InstalledFindResult -> IO (Maybe InstalledFindResult)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe InstalledFindResult -> IO (Maybe InstalledFindResult))
-> Maybe InstalledFindResult -> IO (Maybe InstalledFindResult)
forall a b. (a -> b) -> a -> b
$! FinderCache -> InstalledModule -> Maybe InstalledFindResult
forall a. InstalledModuleEnv a -> InstalledModule -> Maybe a
lookupInstalledModuleEnv FinderCache
c InstalledModule
key
findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findImportedModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
mb_pkg =
case Maybe FastString
mb_pkg of
Maybe FastString
Nothing -> IO FindResult
unqual_import
Just FastString
pkg | FastString
pkg FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== String -> FastString
fsLit String
"this" -> IO FindResult
home_import
| Bool
otherwise -> IO FindResult
pkg_import
where
home_import :: IO FindResult
home_import = HscEnv -> ModuleName -> IO FindResult
findHomeModule HscEnv
hsc_env ModuleName
mod_name
pkg_import :: IO FindResult
pkg_import = HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findExposedPackageModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
mb_pkg
unqual_import :: IO FindResult
unqual_import = IO FindResult
home_import
IO FindResult -> IO FindResult -> IO FindResult
forall (m :: * -> *).
Monad m =>
m FindResult -> m FindResult -> m FindResult
`orIfNotFound`
HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findExposedPackageModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
forall a. Maybe a
Nothing
findPluginModule :: HscEnv -> ModuleName -> IO FindResult
findPluginModule :: HscEnv -> ModuleName -> IO FindResult
findPluginModule HscEnv
hsc_env ModuleName
mod_name =
HscEnv -> ModuleName -> IO FindResult
findHomeModule HscEnv
hsc_env ModuleName
mod_name
IO FindResult -> IO FindResult -> IO FindResult
forall (m :: * -> *).
Monad m =>
m FindResult -> m FindResult -> m FindResult
`orIfNotFound`
HscEnv -> ModuleName -> IO FindResult
findExposedPluginPackageModule HscEnv
hsc_env ModuleName
mod_name
findExactModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
findExactModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
findExactModule HscEnv
hsc_env InstalledModule
mod =
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
in if InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit InstalledModule
mod UnitId -> Unit -> Bool
`unitIdEq` DynFlags -> Unit
homeUnit DynFlags
dflags
then HscEnv -> ModuleName -> IO InstalledFindResult
findInstalledHomeModule HscEnv
hsc_env (InstalledModule -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName InstalledModule
mod)
else HscEnv -> InstalledModule -> IO InstalledFindResult
findPackageModule HscEnv
hsc_env InstalledModule
mod
orIfNotFound :: Monad m => m FindResult -> m FindResult -> m FindResult
orIfNotFound :: forall (m :: * -> *).
Monad m =>
m FindResult -> m FindResult -> m FindResult
orIfNotFound m FindResult
this m FindResult
or_this = do
FindResult
res <- m FindResult
this
case FindResult
res of
NotFound { fr_paths :: FindResult -> [String]
fr_paths = [String]
paths1, fr_mods_hidden :: FindResult -> [Unit]
fr_mods_hidden = [Unit]
mh1
, fr_pkgs_hidden :: FindResult -> [Unit]
fr_pkgs_hidden = [Unit]
ph1, fr_unusables :: FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
u1, fr_suggestions :: FindResult -> [ModuleSuggestion]
fr_suggestions = [ModuleSuggestion]
s1 }
-> do FindResult
res2 <- m FindResult
or_this
case FindResult
res2 of
NotFound { fr_paths :: FindResult -> [String]
fr_paths = [String]
paths2, fr_pkg :: FindResult -> Maybe Unit
fr_pkg = Maybe Unit
mb_pkg2, fr_mods_hidden :: FindResult -> [Unit]
fr_mods_hidden = [Unit]
mh2
, fr_pkgs_hidden :: FindResult -> [Unit]
fr_pkgs_hidden = [Unit]
ph2, fr_unusables :: FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
u2
, fr_suggestions :: FindResult -> [ModuleSuggestion]
fr_suggestions = [ModuleSuggestion]
s2 }
-> FindResult -> m FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (NotFound :: [String]
-> Maybe Unit
-> [Unit]
-> [Unit]
-> [(Unit, UnusableUnitReason)]
-> [ModuleSuggestion]
-> FindResult
NotFound { fr_paths :: [String]
fr_paths = [String]
paths1 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
paths2
, fr_pkg :: Maybe Unit
fr_pkg = Maybe Unit
mb_pkg2
, fr_mods_hidden :: [Unit]
fr_mods_hidden = [Unit]
mh1 [Unit] -> [Unit] -> [Unit]
forall a. [a] -> [a] -> [a]
++ [Unit]
mh2
, fr_pkgs_hidden :: [Unit]
fr_pkgs_hidden = [Unit]
ph1 [Unit] -> [Unit] -> [Unit]
forall a. [a] -> [a] -> [a]
++ [Unit]
ph2
, fr_unusables :: [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
u1 [(Unit, UnusableUnitReason)]
-> [(Unit, UnusableUnitReason)] -> [(Unit, UnusableUnitReason)]
forall a. [a] -> [a] -> [a]
++ [(Unit, UnusableUnitReason)]
u2
, fr_suggestions :: [ModuleSuggestion]
fr_suggestions = [ModuleSuggestion]
s1 [ModuleSuggestion] -> [ModuleSuggestion] -> [ModuleSuggestion]
forall a. [a] -> [a] -> [a]
++ [ModuleSuggestion]
s2 })
FindResult
_other -> FindResult -> m FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return FindResult
res2
FindResult
_other -> FindResult -> m FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return FindResult
res
homeSearchCache :: HscEnv -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
homeSearchCache :: HscEnv
-> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
homeSearchCache HscEnv
hsc_env ModuleName
mod_name IO InstalledFindResult
do_this = do
let mod :: InstalledModule
mod = DynFlags -> ModuleName -> InstalledModule
mkHomeInstalledModule (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) ModuleName
mod_name
HscEnv
-> InstalledModule
-> IO InstalledFindResult
-> IO InstalledFindResult
modLocationCache HscEnv
hsc_env InstalledModule
mod IO InstalledFindResult
do_this
findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
-> IO FindResult
findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findExposedPackageModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
mb_pkg
= HscEnv -> LookupResult -> IO FindResult
findLookupResult HscEnv
hsc_env
(LookupResult -> IO FindResult) -> LookupResult -> IO FindResult
forall a b. (a -> b) -> a -> b
$ UnitState -> ModuleName -> Maybe FastString -> LookupResult
lookupModuleWithSuggestions
(DynFlags -> UnitState
unitState (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)) ModuleName
mod_name Maybe FastString
mb_pkg
findExposedPluginPackageModule :: HscEnv -> ModuleName
-> IO FindResult
findExposedPluginPackageModule :: HscEnv -> ModuleName -> IO FindResult
findExposedPluginPackageModule HscEnv
hsc_env ModuleName
mod_name
= HscEnv -> LookupResult -> IO FindResult
findLookupResult HscEnv
hsc_env
(LookupResult -> IO FindResult) -> LookupResult -> IO FindResult
forall a b. (a -> b) -> a -> b
$ UnitState -> ModuleName -> Maybe FastString -> LookupResult
lookupPluginModuleWithSuggestions
(DynFlags -> UnitState
unitState (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)) ModuleName
mod_name Maybe FastString
forall a. Maybe a
Nothing
findLookupResult :: HscEnv -> LookupResult -> IO FindResult
findLookupResult :: HscEnv -> LookupResult -> IO FindResult
findLookupResult HscEnv
hsc_env LookupResult
r = case LookupResult
r of
LookupFound GenModule Unit
m (UnitInfo, ModuleOrigin)
pkg_conf -> do
let im :: InstalledModule
im = (InstalledModule, Maybe InstantiatedModule) -> InstalledModule
forall a b. (a, b) -> a
fst (GenModule Unit -> (InstalledModule, Maybe InstantiatedModule)
getModuleInstantiation GenModule Unit
m)
InstalledFindResult
r' <- HscEnv -> InstalledModule -> UnitInfo -> IO InstalledFindResult
findPackageModule_ HscEnv
hsc_env InstalledModule
im ((UnitInfo, ModuleOrigin) -> UnitInfo
forall a b. (a, b) -> a
fst (UnitInfo, ModuleOrigin)
pkg_conf)
case InstalledFindResult
r' of
InstalledFound ModLocation
loc InstalledModule
_ -> FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation -> GenModule Unit -> FindResult
Found ModLocation
loc GenModule Unit
m)
InstalledNoPackage UnitId
_ -> FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (Unit -> FindResult
NoPackage (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
m))
InstalledNotFound [String]
fp Maybe UnitId
_ -> FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (NotFound :: [String]
-> Maybe Unit
-> [Unit]
-> [Unit]
-> [(Unit, UnusableUnitReason)]
-> [ModuleSuggestion]
-> FindResult
NotFound{ fr_paths :: [String]
fr_paths = [String]
fp, fr_pkg :: Maybe Unit
fr_pkg = Unit -> Maybe Unit
forall a. a -> Maybe a
Just (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
m)
, fr_pkgs_hidden :: [Unit]
fr_pkgs_hidden = []
, fr_mods_hidden :: [Unit]
fr_mods_hidden = []
, fr_unusables :: [(Unit, UnusableUnitReason)]
fr_unusables = []
, fr_suggestions :: [ModuleSuggestion]
fr_suggestions = []})
LookupMultiple [(GenModule Unit, ModuleOrigin)]
rs ->
FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return ([(GenModule Unit, ModuleOrigin)] -> FindResult
FoundMultiple [(GenModule Unit, ModuleOrigin)]
rs)
LookupHidden [(GenModule Unit, ModuleOrigin)]
pkg_hiddens [(GenModule Unit, ModuleOrigin)]
mod_hiddens ->
FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (NotFound :: [String]
-> Maybe Unit
-> [Unit]
-> [Unit]
-> [(Unit, UnusableUnitReason)]
-> [ModuleSuggestion]
-> FindResult
NotFound{ fr_paths :: [String]
fr_paths = [], fr_pkg :: Maybe Unit
fr_pkg = Maybe Unit
forall a. Maybe a
Nothing
, fr_pkgs_hidden :: [Unit]
fr_pkgs_hidden = ((GenModule Unit, ModuleOrigin) -> Unit)
-> [(GenModule Unit, ModuleOrigin)] -> [Unit]
forall a b. (a -> b) -> [a] -> [b]
map (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit(GenModule Unit -> Unit)
-> ((GenModule Unit, ModuleOrigin) -> GenModule Unit)
-> (GenModule Unit, ModuleOrigin)
-> Unit
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenModule Unit, ModuleOrigin) -> GenModule Unit
forall a b. (a, b) -> a
fst) [(GenModule Unit, ModuleOrigin)]
pkg_hiddens
, fr_mods_hidden :: [Unit]
fr_mods_hidden = ((GenModule Unit, ModuleOrigin) -> Unit)
-> [(GenModule Unit, ModuleOrigin)] -> [Unit]
forall a b. (a -> b) -> [a] -> [b]
map (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit(GenModule Unit -> Unit)
-> ((GenModule Unit, ModuleOrigin) -> GenModule Unit)
-> (GenModule Unit, ModuleOrigin)
-> Unit
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenModule Unit, ModuleOrigin) -> GenModule Unit
forall a b. (a, b) -> a
fst) [(GenModule Unit, ModuleOrigin)]
mod_hiddens
, fr_unusables :: [(Unit, UnusableUnitReason)]
fr_unusables = []
, fr_suggestions :: [ModuleSuggestion]
fr_suggestions = [] })
LookupUnusable [(GenModule Unit, ModuleOrigin)]
unusable ->
let unusables' :: [(Unit, UnusableUnitReason)]
unusables' = ((GenModule Unit, ModuleOrigin) -> (Unit, UnusableUnitReason))
-> [(GenModule Unit, ModuleOrigin)] -> [(Unit, UnusableUnitReason)]
forall a b. (a -> b) -> [a] -> [b]
map (GenModule Unit, ModuleOrigin) -> (Unit, UnusableUnitReason)
forall {a}. (GenModule a, ModuleOrigin) -> (a, UnusableUnitReason)
get_unusable [(GenModule Unit, ModuleOrigin)]
unusable
get_unusable :: (GenModule a, ModuleOrigin) -> (a, UnusableUnitReason)
get_unusable (GenModule a
m, ModUnusable UnusableUnitReason
r) = (GenModule a -> a
forall unit. GenModule unit -> unit
moduleUnit GenModule a
m, UnusableUnitReason
r)
get_unusable (GenModule a
_, ModuleOrigin
r) =
String -> SDoc -> (a, UnusableUnitReason)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"findLookupResult: unexpected origin" (ModuleOrigin -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleOrigin
r)
in FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (NotFound :: [String]
-> Maybe Unit
-> [Unit]
-> [Unit]
-> [(Unit, UnusableUnitReason)]
-> [ModuleSuggestion]
-> FindResult
NotFound{ fr_paths :: [String]
fr_paths = [], fr_pkg :: Maybe Unit
fr_pkg = Maybe Unit
forall a. Maybe a
Nothing
, fr_pkgs_hidden :: [Unit]
fr_pkgs_hidden = []
, fr_mods_hidden :: [Unit]
fr_mods_hidden = []
, fr_unusables :: [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
unusables'
, fr_suggestions :: [ModuleSuggestion]
fr_suggestions = [] })
LookupNotFound [ModuleSuggestion]
suggest -> do
let suggest' :: [ModuleSuggestion]
suggest'
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_HelpfulErrors (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) = [ModuleSuggestion]
suggest
| Bool
otherwise = []
FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (NotFound :: [String]
-> Maybe Unit
-> [Unit]
-> [Unit]
-> [(Unit, UnusableUnitReason)]
-> [ModuleSuggestion]
-> FindResult
NotFound{ fr_paths :: [String]
fr_paths = [], fr_pkg :: Maybe Unit
fr_pkg = Maybe Unit
forall a. Maybe a
Nothing
, fr_pkgs_hidden :: [Unit]
fr_pkgs_hidden = []
, fr_mods_hidden :: [Unit]
fr_mods_hidden = []
, fr_unusables :: [(Unit, UnusableUnitReason)]
fr_unusables = []
, fr_suggestions :: [ModuleSuggestion]
fr_suggestions = [ModuleSuggestion]
suggest' })
modLocationCache :: HscEnv -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
modLocationCache :: HscEnv
-> InstalledModule
-> IO InstalledFindResult
-> IO InstalledFindResult
modLocationCache HscEnv
hsc_env InstalledModule
mod IO InstalledFindResult
do_this = do
Maybe InstalledFindResult
m <- IORef FinderCache
-> InstalledModule -> IO (Maybe InstalledFindResult)
lookupFinderCache (HscEnv -> IORef FinderCache
hsc_FC HscEnv
hsc_env) InstalledModule
mod
case Maybe InstalledFindResult
m of
Just InstalledFindResult
result -> InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return InstalledFindResult
result
Maybe InstalledFindResult
Nothing -> do
InstalledFindResult
result <- IO InstalledFindResult
do_this
IORef FinderCache
-> InstalledModule -> InstalledFindResult -> IO ()
addToFinderCache (HscEnv -> IORef FinderCache
hsc_FC HscEnv
hsc_env) InstalledModule
mod InstalledFindResult
result
InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return InstalledFindResult
result
mkHomeInstalledModule :: DynFlags -> ModuleName -> InstalledModule
mkHomeInstalledModule :: DynFlags -> ModuleName -> InstalledModule
mkHomeInstalledModule DynFlags
dflags ModuleName
mod_name =
let iuid :: UnitId
iuid = DynFlags -> UnitId
homeUnitId DynFlags
dflags
in UnitId -> ModuleName -> InstalledModule
forall unit. unit -> ModuleName -> GenModule unit
Module UnitId
iuid ModuleName
mod_name
addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO (GenModule Unit)
addHomeModuleToFinder HscEnv
hsc_env ModuleName
mod_name ModLocation
loc = do
let mod :: InstalledModule
mod = DynFlags -> ModuleName -> InstalledModule
mkHomeInstalledModule (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) ModuleName
mod_name
IORef FinderCache
-> InstalledModule -> InstalledFindResult -> IO ()
addToFinderCache (HscEnv -> IORef FinderCache
hsc_FC HscEnv
hsc_env) InstalledModule
mod (ModLocation -> InstalledModule -> InstalledFindResult
InstalledFound ModLocation
loc InstalledModule
mod)
GenModule Unit -> IO (GenModule Unit)
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags -> ModuleName -> GenModule Unit
mkHomeModule (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) ModuleName
mod_name)
uncacheModule :: HscEnv -> ModuleName -> IO ()
uncacheModule :: HscEnv -> ModuleName -> IO ()
uncacheModule HscEnv
hsc_env ModuleName
mod_name = do
let mod :: InstalledModule
mod = DynFlags -> ModuleName -> InstalledModule
mkHomeInstalledModule (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) ModuleName
mod_name
IORef FinderCache -> InstalledModule -> IO ()
removeFromFinderCache (HscEnv -> IORef FinderCache
hsc_FC HscEnv
hsc_env) InstalledModule
mod
findHomeModule :: HscEnv -> ModuleName -> IO FindResult
findHomeModule :: HscEnv -> ModuleName -> IO FindResult
findHomeModule HscEnv
hsc_env ModuleName
mod_name = do
InstalledFindResult
r <- HscEnv -> ModuleName -> IO InstalledFindResult
findInstalledHomeModule HscEnv
hsc_env ModuleName
mod_name
FindResult -> IO FindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (FindResult -> IO FindResult) -> FindResult -> IO FindResult
forall a b. (a -> b) -> a -> b
$ case InstalledFindResult
r of
InstalledFound ModLocation
loc InstalledModule
_ -> ModLocation -> GenModule Unit -> FindResult
Found ModLocation
loc (Unit -> ModuleName -> GenModule Unit
forall unit. unit -> ModuleName -> GenModule unit
mkModule Unit
uid ModuleName
mod_name)
InstalledNoPackage UnitId
_ -> Unit -> FindResult
NoPackage Unit
uid
InstalledNotFound [String]
fps Maybe UnitId
_ -> NotFound :: [String]
-> Maybe Unit
-> [Unit]
-> [Unit]
-> [(Unit, UnusableUnitReason)]
-> [ModuleSuggestion]
-> FindResult
NotFound {
fr_paths :: [String]
fr_paths = [String]
fps,
fr_pkg :: Maybe Unit
fr_pkg = Unit -> Maybe Unit
forall a. a -> Maybe a
Just Unit
uid,
fr_mods_hidden :: [Unit]
fr_mods_hidden = [],
fr_pkgs_hidden :: [Unit]
fr_pkgs_hidden = [],
fr_unusables :: [(Unit, UnusableUnitReason)]
fr_unusables = [],
fr_suggestions :: [ModuleSuggestion]
fr_suggestions = []
}
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
uid :: Unit
uid = DynFlags -> Unit
homeUnit DynFlags
dflags
findInstalledHomeModule :: HscEnv -> ModuleName -> IO InstalledFindResult
findInstalledHomeModule :: HscEnv -> ModuleName -> IO InstalledFindResult
findInstalledHomeModule HscEnv
hsc_env ModuleName
mod_name =
HscEnv
-> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
homeSearchCache HscEnv
hsc_env ModuleName
mod_name (IO InstalledFindResult -> IO InstalledFindResult)
-> IO InstalledFindResult -> IO InstalledFindResult
forall a b. (a -> b) -> a -> b
$
let
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
home_path :: [String]
home_path = DynFlags -> [String]
importPaths DynFlags
dflags
hisuf :: String
hisuf = DynFlags -> String
hiSuf DynFlags
dflags
mod :: InstalledModule
mod = DynFlags -> ModuleName -> InstalledModule
mkHomeInstalledModule DynFlags
dflags ModuleName
mod_name
source_exts :: [(String, String -> String -> IO ModLocation)]
source_exts =
[ (String
"hs", DynFlags
-> ModuleName -> String -> String -> String -> IO ModLocation
mkHomeModLocationSearched DynFlags
dflags ModuleName
mod_name String
"hs")
, (String
"lhs", DynFlags
-> ModuleName -> String -> String -> String -> IO ModLocation
mkHomeModLocationSearched DynFlags
dflags ModuleName
mod_name String
"lhs")
, (String
"hsig", DynFlags
-> ModuleName -> String -> String -> String -> IO ModLocation
mkHomeModLocationSearched DynFlags
dflags ModuleName
mod_name String
"hsig")
, (String
"lhsig", DynFlags
-> ModuleName -> String -> String -> String -> IO ModLocation
mkHomeModLocationSearched DynFlags
dflags ModuleName
mod_name String
"lhsig")
]
hi_exts :: [(String, String -> String -> IO ModLocation)]
hi_exts = [ (String
hisuf, DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModHiOnlyLocation DynFlags
dflags ModuleName
mod_name)
, (String -> String
addBootSuffix String
hisuf, DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModHiOnlyLocation DynFlags
dflags ModuleName
mod_name)
]
exts :: [(String, String -> String -> IO ModLocation)]
exts | GhcMode -> Bool
isOneShot (DynFlags -> GhcMode
ghcMode DynFlags
dflags) = [(String, String -> String -> IO ModLocation)]
hi_exts
| Bool
otherwise = [(String, String -> String -> IO ModLocation)]
source_exts
in
if InstalledModule
mod InstalledModule -> GenModule Unit -> Bool
`installedModuleEq` GenModule Unit
gHC_PRIM
then InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation -> InstalledModule -> InstalledFindResult
InstalledFound (String -> ModLocation
forall a. HasCallStack => String -> a
error String
"GHC.Prim ModLocation") InstalledModule
mod)
else [String]
-> InstalledModule
-> [(String, String -> String -> IO ModLocation)]
-> IO InstalledFindResult
searchPathExts [String]
home_path InstalledModule
mod [(String, String -> String -> IO ModLocation)]
exts
findPackageModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
findPackageModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
findPackageModule HscEnv
hsc_env InstalledModule
mod = do
let
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
pkg_id :: UnitId
pkg_id = InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit InstalledModule
mod
pkgstate :: UnitState
pkgstate = DynFlags -> UnitState
unitState DynFlags
dflags
case UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId UnitState
pkgstate UnitId
pkg_id of
Maybe UnitInfo
Nothing -> InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (UnitId -> InstalledFindResult
InstalledNoPackage UnitId
pkg_id)
Just UnitInfo
pkg_conf -> HscEnv -> InstalledModule -> UnitInfo -> IO InstalledFindResult
findPackageModule_ HscEnv
hsc_env InstalledModule
mod UnitInfo
pkg_conf
findPackageModule_ :: HscEnv -> InstalledModule -> UnitInfo -> IO InstalledFindResult
findPackageModule_ :: HscEnv -> InstalledModule -> UnitInfo -> IO InstalledFindResult
findPackageModule_ HscEnv
hsc_env InstalledModule
mod UnitInfo
pkg_conf =
ASSERT2( moduleUnit mod == unitId pkg_conf, ppr (moduleUnit mod) <+> ppr (unitId pkg_conf) )
HscEnv
-> InstalledModule
-> IO InstalledFindResult
-> IO InstalledFindResult
modLocationCache HscEnv
hsc_env InstalledModule
mod (IO InstalledFindResult -> IO InstalledFindResult)
-> IO InstalledFindResult -> IO InstalledFindResult
forall a b. (a -> b) -> a -> b
$
if InstalledModule
mod InstalledModule -> GenModule Unit -> Bool
`installedModuleEq` GenModule Unit
gHC_PRIM
then InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation -> InstalledModule -> InstalledFindResult
InstalledFound (String -> ModLocation
forall a. HasCallStack => String -> a
error String
"GHC.Prim ModLocation") InstalledModule
mod)
else
let
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
tag :: String
tag = Set Way -> String
waysBuildTag (DynFlags -> Set Way
ways DynFlags
dflags)
package_hisuf :: String
package_hisuf | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
tag = String
"hi"
| Bool
otherwise = String
tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_hi"
mk_hi_loc :: String -> String -> IO ModLocation
mk_hi_loc = DynFlags -> String -> String -> String -> IO ModLocation
mkHiOnlyModLocation DynFlags
dflags String
package_hisuf
import_dirs :: [String]
import_dirs = UnitInfo -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitImportDirs UnitInfo
pkg_conf
in
case [String]
import_dirs of
[String
one] | GhcMode
MkDepend <- DynFlags -> GhcMode
ghcMode DynFlags
dflags -> do
let basename :: String
basename = ModuleName -> String
moduleNameSlashes (InstalledModule -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName InstalledModule
mod)
ModLocation
loc <- String -> String -> IO ModLocation
mk_hi_loc String
one String
basename
InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation -> InstalledModule -> InstalledFindResult
InstalledFound ModLocation
loc InstalledModule
mod)
[String]
_otherwise ->
[String]
-> InstalledModule
-> [(String, String -> String -> IO ModLocation)]
-> IO InstalledFindResult
searchPathExts [String]
import_dirs InstalledModule
mod [(String
package_hisuf, String -> String -> IO ModLocation
mk_hi_loc)]
searchPathExts
:: [FilePath]
-> InstalledModule
-> [ (
FileExt,
FilePath -> BaseName -> IO ModLocation
)
]
-> IO InstalledFindResult
searchPathExts :: [String]
-> InstalledModule
-> [(String, String -> String -> IO ModLocation)]
-> IO InstalledFindResult
searchPathExts [String]
paths InstalledModule
mod [(String, String -> String -> IO ModLocation)]
exts
= do InstalledFindResult
result <- [(String, IO ModLocation)] -> IO InstalledFindResult
search [(String, IO ModLocation)]
to_search
InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return InstalledFindResult
result
where
basename :: String
basename = ModuleName -> String
moduleNameSlashes (InstalledModule -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName InstalledModule
mod)
to_search :: [(FilePath, IO ModLocation)]
to_search :: [(String, IO ModLocation)]
to_search = [ (String
file, String -> String -> IO ModLocation
fn String
path String
basename)
| String
path <- [String]
paths,
(String
ext,String -> String -> IO ModLocation
fn) <- [(String, String -> String -> IO ModLocation)]
exts,
let base :: String
base | String
path String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"." = String
basename
| Bool
otherwise = String
path String -> String -> String
</> String
basename
file :: String
file = String
base String -> String -> String
<.> String
ext
]
search :: [(String, IO ModLocation)] -> IO InstalledFindResult
search [] = InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> Maybe UnitId -> InstalledFindResult
InstalledNotFound (((String, IO ModLocation) -> String)
-> [(String, IO ModLocation)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, IO ModLocation) -> String
forall a b. (a, b) -> a
fst [(String, IO ModLocation)]
to_search) (UnitId -> Maybe UnitId
forall a. a -> Maybe a
Just (InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit InstalledModule
mod)))
search ((String
file, IO ModLocation
mk_result) : [(String, IO ModLocation)]
rest) = do
Bool
b <- String -> IO Bool
doesFileExist String
file
if Bool
b
then do { ModLocation
loc <- IO ModLocation
mk_result; InstalledFindResult -> IO InstalledFindResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation -> InstalledModule -> InstalledFindResult
InstalledFound ModLocation
loc InstalledModule
mod) }
else [(String, IO ModLocation)] -> IO InstalledFindResult
search [(String, IO ModLocation)]
rest
mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt
-> FilePath -> BaseName -> IO ModLocation
mkHomeModLocationSearched :: DynFlags
-> ModuleName -> String -> String -> String -> IO ModLocation
mkHomeModLocationSearched DynFlags
dflags ModuleName
mod String
suff String
path String
basename = do
DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags ModuleName
mod (String
path String -> String -> String
</> String
basename) String
suff
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
mkHomeModLocation :: DynFlags -> ModuleName -> String -> IO ModLocation
mkHomeModLocation DynFlags
dflags ModuleName
mod String
src_filename = do
let (String
basename,String
extension) = String -> (String, String)
splitExtension String
src_filename
DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags ModuleName
mod String
basename String
extension
mkHomeModLocation2 :: DynFlags
-> ModuleName
-> FilePath
-> String
-> IO ModLocation
mkHomeModLocation2 :: DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags ModuleName
mod String
src_basename String
ext = do
let mod_basename :: String
mod_basename = ModuleName -> String
moduleNameSlashes ModuleName
mod
obj_fn :: String
obj_fn = DynFlags -> String -> String -> String
mkObjPath DynFlags
dflags String
src_basename String
mod_basename
hi_fn :: String
hi_fn = DynFlags -> String -> String -> String
mkHiPath DynFlags
dflags String
src_basename String
mod_basename
hie_fn :: String
hie_fn = DynFlags -> String -> String -> String
mkHiePath DynFlags
dflags String
src_basename String
mod_basename
ModLocation -> IO ModLocation
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation :: Maybe String -> String -> String -> String -> ModLocation
ModLocation{ ml_hs_file :: Maybe String
ml_hs_file = String -> Maybe String
forall a. a -> Maybe a
Just (String
src_basename String -> String -> String
<.> String
ext),
ml_hi_file :: String
ml_hi_file = String
hi_fn,
ml_obj_file :: String
ml_obj_file = String
obj_fn,
ml_hie_file :: String
ml_hie_file = String
hie_fn })
mkHomeModHiOnlyLocation :: DynFlags
-> ModuleName
-> FilePath
-> BaseName
-> IO ModLocation
mkHomeModHiOnlyLocation :: DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModHiOnlyLocation DynFlags
dflags ModuleName
mod String
path String
basename = do
ModLocation
loc <- DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags ModuleName
mod (String
path String -> String -> String
</> String
basename) String
""
ModLocation -> IO ModLocation
forall (m :: * -> *) a. Monad m => a -> m a
return ModLocation
loc { ml_hs_file :: Maybe String
ml_hs_file = Maybe String
forall a. Maybe a
Nothing }
mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
-> IO ModLocation
mkHiOnlyModLocation :: DynFlags -> String -> String -> String -> IO ModLocation
mkHiOnlyModLocation DynFlags
dflags String
hisuf String
path String
basename
= do let full_basename :: String
full_basename = String
path String -> String -> String
</> String
basename
obj_fn :: String
obj_fn = DynFlags -> String -> String -> String
mkObjPath DynFlags
dflags String
full_basename String
basename
hie_fn :: String
hie_fn = DynFlags -> String -> String -> String
mkHiePath DynFlags
dflags String
full_basename String
basename
ModLocation -> IO ModLocation
forall (m :: * -> *) a. Monad m => a -> m a
return ModLocation :: Maybe String -> String -> String -> String -> ModLocation
ModLocation{ ml_hs_file :: Maybe String
ml_hs_file = Maybe String
forall a. Maybe a
Nothing,
ml_hi_file :: String
ml_hi_file = String
full_basename String -> String -> String
<.> String
hisuf,
ml_obj_file :: String
ml_obj_file = String
obj_fn,
ml_hie_file :: String
ml_hie_file = String
hie_fn
}
mkObjPath
:: DynFlags
-> FilePath
-> String
-> FilePath
mkObjPath :: DynFlags -> String -> String -> String
mkObjPath DynFlags
dflags String
basename String
mod_basename = String
obj_basename String -> String -> String
<.> String
osuf
where
odir :: Maybe String
odir = DynFlags -> Maybe String
objectDir DynFlags
dflags
osuf :: String
osuf = DynFlags -> String
objectSuf DynFlags
dflags
obj_basename :: String
obj_basename | Just String
dir <- Maybe String
odir = String
dir String -> String -> String
</> String
mod_basename
| Bool
otherwise = String
basename
mkHiPath
:: DynFlags
-> FilePath
-> String
-> FilePath
mkHiPath :: DynFlags -> String -> String -> String
mkHiPath DynFlags
dflags String
basename String
mod_basename = String
hi_basename String -> String -> String
<.> String
hisuf
where
hidir :: Maybe String
hidir = DynFlags -> Maybe String
hiDir DynFlags
dflags
hisuf :: String
hisuf = DynFlags -> String
hiSuf DynFlags
dflags
hi_basename :: String
hi_basename | Just String
dir <- Maybe String
hidir = String
dir String -> String -> String
</> String
mod_basename
| Bool
otherwise = String
basename
mkHiePath
:: DynFlags
-> FilePath
-> String
-> FilePath
mkHiePath :: DynFlags -> String -> String -> String
mkHiePath DynFlags
dflags String
basename String
mod_basename = String
hie_basename String -> String -> String
<.> String
hiesuf
where
hiedir :: Maybe String
hiedir = DynFlags -> Maybe String
hieDir DynFlags
dflags
hiesuf :: String
hiesuf = DynFlags -> String
hieSuf DynFlags
dflags
hie_basename :: String
hie_basename | Just String
dir <- Maybe String
hiedir = String
dir String -> String -> String
</> String
mod_basename
| Bool
otherwise = String
basename
mkStubPaths
:: DynFlags
-> ModuleName
-> ModLocation
-> FilePath
mkStubPaths :: DynFlags -> ModuleName -> ModLocation -> String
mkStubPaths DynFlags
dflags ModuleName
mod ModLocation
location
= let
stubdir :: Maybe String
stubdir = DynFlags -> Maybe String
stubDir DynFlags
dflags
mod_basename :: String
mod_basename = ModuleName -> String
moduleNameSlashes ModuleName
mod
src_basename :: String
src_basename = String -> String
dropExtension (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> String
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"mkStubPaths"
(ModLocation -> Maybe String
ml_hs_file ModLocation
location)
stub_basename0 :: String
stub_basename0
| Just String
dir <- Maybe String
stubdir = String
dir String -> String -> String
</> String
mod_basename
| Bool
otherwise = String
src_basename
stub_basename :: String
stub_basename = String
stub_basename0 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_stub"
in
String
stub_basename String -> String -> String
<.> String
"h"
findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
findObjectLinkableMaybe :: GenModule Unit -> ModLocation -> IO (Maybe Linkable)
findObjectLinkableMaybe GenModule Unit
mod ModLocation
locn
= do let obj_fn :: String
obj_fn = ModLocation -> String
ml_obj_file ModLocation
locn
Maybe UTCTime
maybe_obj_time <- String -> IO (Maybe UTCTime)
modificationTimeIfExists String
obj_fn
case Maybe UTCTime
maybe_obj_time of
Maybe UTCTime
Nothing -> Maybe Linkable -> IO (Maybe Linkable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Linkable
forall a. Maybe a
Nothing
Just UTCTime
obj_time -> (Linkable -> Maybe Linkable) -> IO Linkable -> IO (Maybe Linkable)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just (GenModule Unit -> String -> UTCTime -> IO Linkable
findObjectLinkable GenModule Unit
mod String
obj_fn UTCTime
obj_time)
findObjectLinkable :: Module -> FilePath -> UTCTime -> IO Linkable
findObjectLinkable :: GenModule Unit -> String -> UTCTime -> IO Linkable
findObjectLinkable GenModule Unit
mod String
obj_fn UTCTime
obj_time = Linkable -> IO Linkable
forall (m :: * -> *) a. Monad m => a -> m a
return (UTCTime -> GenModule Unit -> [Unlinked] -> Linkable
LM UTCTime
obj_time GenModule Unit
mod [String -> Unlinked
DotO String
obj_fn])
cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
cannotFindModule DynFlags
flags ModuleName
mod FindResult
res =
PtrString
-> PtrString -> DynFlags -> ModuleName -> FindResult -> SDoc
cantFindErr (String -> PtrString
sLit String
cannotFindMsg)
(String -> PtrString
sLit String
"Ambiguous module name")
DynFlags
flags ModuleName
mod FindResult
res
where
cannotFindMsg :: String
cannotFindMsg =
case FindResult
res of
NotFound { fr_mods_hidden :: FindResult -> [Unit]
fr_mods_hidden = [Unit]
hidden_mods
, fr_pkgs_hidden :: FindResult -> [Unit]
fr_pkgs_hidden = [Unit]
hidden_pkgs
, fr_unusables :: FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
unusables }
| Bool -> Bool
not ([Unit] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
hidden_mods Bool -> Bool -> Bool
&& [Unit] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
hidden_pkgs Bool -> Bool -> Bool
&& [(Unit, UnusableUnitReason)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Unit, UnusableUnitReason)]
unusables)
-> String
"Could not load module"
FindResult
_ -> String
"Could not find module"
cannotFindInterface :: DynFlags -> ModuleName -> InstalledFindResult -> SDoc
cannotFindInterface :: DynFlags -> ModuleName -> InstalledFindResult -> SDoc
cannotFindInterface = PtrString
-> PtrString
-> DynFlags
-> ModuleName
-> InstalledFindResult
-> SDoc
cantFindInstalledErr (String -> PtrString
sLit String
"Failed to load interface for")
(String -> PtrString
sLit String
"Ambiguous interface for")
cantFindErr :: PtrString -> PtrString -> DynFlags -> ModuleName -> FindResult
-> SDoc
cantFindErr :: PtrString
-> PtrString -> DynFlags -> ModuleName -> FindResult -> SDoc
cantFindErr PtrString
_ PtrString
multiple_found DynFlags
_ ModuleName
mod_name (FoundMultiple [(GenModule Unit, ModuleOrigin)]
mods)
| Just [Unit]
pkgs <- Maybe [Unit]
unambiguousPackages
= SDoc -> Int -> SDoc -> SDoc
hang (PtrString -> SDoc
ptext PtrString
multiple_found SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name) SDoc -> SDoc -> SDoc
<> SDoc
colon) Int
2 (
[SDoc] -> SDoc
sep [String -> SDoc
text String
"it was found in multiple packages:",
[SDoc] -> SDoc
hsep ((Unit -> SDoc) -> [Unit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Unit]
pkgs) ]
)
| Bool
otherwise
= SDoc -> Int -> SDoc -> SDoc
hang (PtrString -> SDoc
ptext PtrString
multiple_found SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name) SDoc -> SDoc -> SDoc
<> SDoc
colon) Int
2 (
[SDoc] -> SDoc
vcat (((GenModule Unit, ModuleOrigin) -> SDoc)
-> [(GenModule Unit, ModuleOrigin)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (GenModule Unit, ModuleOrigin) -> SDoc
forall {a}.
(Outputable a, Outputable (GenModule a)) =>
(GenModule a, ModuleOrigin) -> SDoc
pprMod [(GenModule Unit, ModuleOrigin)]
mods)
)
where
unambiguousPackages :: Maybe [Unit]
unambiguousPackages = (Maybe [Unit] -> (GenModule Unit, ModuleOrigin) -> Maybe [Unit])
-> Maybe [Unit] -> [(GenModule Unit, ModuleOrigin)] -> Maybe [Unit]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Maybe [Unit] -> (GenModule Unit, ModuleOrigin) -> Maybe [Unit]
forall {a}. Maybe [a] -> (GenModule a, ModuleOrigin) -> Maybe [a]
unambiguousPackage ([Unit] -> Maybe [Unit]
forall a. a -> Maybe a
Just []) [(GenModule Unit, ModuleOrigin)]
mods
unambiguousPackage :: Maybe [a] -> (GenModule a, ModuleOrigin) -> Maybe [a]
unambiguousPackage (Just [a]
xs) (GenModule a
m, ModOrigin (Just Bool
_) [UnitInfo]
_ [UnitInfo]
_ Bool
_)
= [a] -> Maybe [a]
forall a. a -> Maybe a
Just (GenModule a -> a
forall unit. GenModule unit -> unit
moduleUnit GenModule a
m a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs)
unambiguousPackage Maybe [a]
_ (GenModule a, ModuleOrigin)
_ = Maybe [a]
forall a. Maybe a
Nothing
pprMod :: (GenModule a, ModuleOrigin) -> SDoc
pprMod (GenModule a
m, ModuleOrigin
o) = String -> SDoc
text String
"it is bound as" SDoc -> SDoc -> SDoc
<+> GenModule a -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule a
m SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"by" SDoc -> SDoc -> SDoc
<+> GenModule a -> ModuleOrigin -> SDoc
forall {a}. Outputable a => GenModule a -> ModuleOrigin -> SDoc
pprOrigin GenModule a
m ModuleOrigin
o
pprOrigin :: GenModule a -> ModuleOrigin -> SDoc
pprOrigin GenModule a
_ ModuleOrigin
ModHidden = String -> SDoc
forall a. String -> a
panic String
"cantFindErr: bound by mod hidden"
pprOrigin GenModule a
_ (ModUnusable UnusableUnitReason
_) = String -> SDoc
forall a. String -> a
panic String
"cantFindErr: bound by mod unusable"
pprOrigin GenModule a
m (ModOrigin Maybe Bool
e [UnitInfo]
res [UnitInfo]
_ Bool
f) = [SDoc] -> SDoc
sep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma (
if Maybe Bool
e Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
then [String -> SDoc
text String
"package" SDoc -> SDoc -> SDoc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule a -> a
forall unit. GenModule unit -> unit
moduleUnit GenModule a
m)]
else [] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++
(UnitInfo -> SDoc) -> [UnitInfo] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> SDoc
text String
"a reexport in package" SDoc -> SDoc -> SDoc
<+>)
(SDoc -> SDoc) -> (UnitInfo -> SDoc) -> UnitInfo -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr(Unit -> SDoc) -> (UnitInfo -> Unit) -> UnitInfo -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.UnitInfo -> Unit
mkUnit) [UnitInfo]
res [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++
if Bool
f then [String -> SDoc
text String
"a package flag"] else []
)
cantFindErr PtrString
cannot_find PtrString
_ DynFlags
dflags ModuleName
mod_name FindResult
find_result
= PtrString -> SDoc
ptext PtrString
cannot_find SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name)
SDoc -> SDoc -> SDoc
$$ SDoc
more_info
where
pkgs :: UnitState
pkgs = DynFlags -> UnitState
unitState DynFlags
dflags
more_info :: SDoc
more_info
= case FindResult
find_result of
NoPackage Unit
pkg
-> String -> SDoc
text String
"no unit id matching" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
pkg) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"was found"
NotFound { fr_paths :: FindResult -> [String]
fr_paths = [String]
files, fr_pkg :: FindResult -> Maybe Unit
fr_pkg = Maybe Unit
mb_pkg
, fr_mods_hidden :: FindResult -> [Unit]
fr_mods_hidden = [Unit]
mod_hiddens, fr_pkgs_hidden :: FindResult -> [Unit]
fr_pkgs_hidden = [Unit]
pkg_hiddens
, fr_unusables :: FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
unusables, fr_suggestions :: FindResult -> [ModuleSuggestion]
fr_suggestions = [ModuleSuggestion]
suggest }
| Just Unit
pkg <- Maybe Unit
mb_pkg, Unit
pkg Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
/= DynFlags -> Unit
homeUnit DynFlags
dflags
-> Unit -> [String] -> SDoc
forall {a}. Outputable a => a -> [String] -> SDoc
not_found_in_package Unit
pkg [String]
files
| Bool -> Bool
not ([ModuleSuggestion] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModuleSuggestion]
suggest)
-> [ModuleSuggestion] -> SDoc
pp_suggestions [ModuleSuggestion]
suggest SDoc -> SDoc -> SDoc
$$ [String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
| [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files Bool -> Bool -> Bool
&& [Unit] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
mod_hiddens Bool -> Bool -> Bool
&&
[Unit] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
pkg_hiddens Bool -> Bool -> Bool
&& [(Unit, UnusableUnitReason)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Unit, UnusableUnitReason)]
unusables
-> String -> SDoc
text String
"It is not a module in the current program, or in any known package."
| Bool
otherwise
-> [SDoc] -> SDoc
vcat ((Unit -> SDoc) -> [Unit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Unit -> SDoc
pkg_hidden [Unit]
pkg_hiddens) SDoc -> SDoc -> SDoc
$$
[SDoc] -> SDoc
vcat ((Unit -> SDoc) -> [Unit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Unit -> SDoc
forall a. Outputable a => a -> SDoc
mod_hidden [Unit]
mod_hiddens) SDoc -> SDoc -> SDoc
$$
[SDoc] -> SDoc
vcat (((Unit, UnusableUnitReason) -> SDoc)
-> [(Unit, UnusableUnitReason)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Unit, UnusableUnitReason) -> SDoc
forall {a}. Outputable a => (a, UnusableUnitReason) -> SDoc
unusable [(Unit, UnusableUnitReason)]
unusables) SDoc -> SDoc -> SDoc
$$
[String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
FindResult
_ -> String -> SDoc
forall a. String -> a
panic String
"cantFindErr"
build_tag :: String
build_tag = Set Way -> String
waysBuildTag (DynFlags -> Set Way
ways DynFlags
dflags)
not_found_in_package :: a -> [String] -> SDoc
not_found_in_package a
pkg [String]
files
| String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
""
= let
build :: String
build = if String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"p" then String
"profiling"
else String
"\"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
build_tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\""
in
String -> SDoc
text String
"Perhaps you haven't installed the " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
build SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" libraries for package " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg) SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'?' SDoc -> SDoc -> SDoc
$$
[String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
| Bool
otherwise
= String -> SDoc
text String
"There are files missing in the " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" package," SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"try running 'ghc-pkg check'." SDoc -> SDoc -> SDoc
$$
[String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
pkg_hidden :: Unit -> SDoc
pkg_hidden :: Unit -> SDoc
pkg_hidden Unit
uid =
String -> SDoc
text String
"It is a member of the hidden package"
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
uid)
SDoc -> SDoc -> SDoc
<> SDoc
dot SDoc -> SDoc -> SDoc
$$ Unit -> SDoc
pkg_hidden_hint Unit
uid
pkg_hidden_hint :: Unit -> SDoc
pkg_hidden_hint Unit
uid
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_BuildingCabalPackage DynFlags
dflags
= let pkg :: UnitInfo
pkg = String -> Maybe UnitInfo -> UnitInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"pkg_hidden" (UnitState -> Unit -> Maybe UnitInfo
lookupUnit UnitState
pkgs Unit
uid)
in String -> SDoc
text String
"Perhaps you need to add" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (PackageName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> PackageName
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
pkg)) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"to the build-depends in your .cabal file."
| Just UnitInfo
pkg <- UnitState -> Unit -> Maybe UnitInfo
lookupUnit UnitState
pkgs Unit
uid
= String -> SDoc
text String
"You can run" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (String -> SDoc
text String
":set -package " SDoc -> SDoc -> SDoc
<> PackageName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> PackageName
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
pkg)) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"to expose it." SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"(Note: this unloads all the modules in the current scope.)"
| Bool
otherwise = SDoc
Outputable.empty
mod_hidden :: a -> SDoc
mod_hidden a
pkg =
String -> SDoc
text String
"it is a hidden module in the package" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg)
unusable :: (a, UnusableUnitReason) -> SDoc
unusable (a
pkg, UnusableUnitReason
reason)
= String -> SDoc
text String
"It is a member of the package"
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg)
SDoc -> SDoc -> SDoc
$$ SDoc -> UnusableUnitReason -> SDoc
pprReason (String -> SDoc
text String
"which is") UnusableUnitReason
reason
pp_suggestions :: [ModuleSuggestion] -> SDoc
pp_suggestions :: [ModuleSuggestion] -> SDoc
pp_suggestions [ModuleSuggestion]
sugs
| [ModuleSuggestion] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModuleSuggestion]
sugs = SDoc
Outputable.empty
| Bool
otherwise = SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Perhaps you meant")
Int
2 ([SDoc] -> SDoc
vcat ((ModuleSuggestion -> SDoc) -> [ModuleSuggestion] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ModuleSuggestion -> SDoc
pp_sugg [ModuleSuggestion]
sugs))
pp_sugg :: ModuleSuggestion -> SDoc
pp_sugg (SuggestVisible ModuleName
m GenModule Unit
mod ModuleOrigin
o) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
m SDoc -> SDoc -> SDoc
<+> ModuleOrigin -> SDoc
provenance ModuleOrigin
o
where provenance :: ModuleOrigin -> SDoc
provenance ModuleOrigin
ModHidden = SDoc
Outputable.empty
provenance (ModUnusable UnusableUnitReason
_) = SDoc
Outputable.empty
provenance (ModOrigin{ fromOrigUnit :: ModuleOrigin -> Maybe Bool
fromOrigUnit = Maybe Bool
e,
fromExposedReexport :: ModuleOrigin -> [UnitInfo]
fromExposedReexport = [UnitInfo]
res,
fromPackageFlag :: ModuleOrigin -> Bool
fromPackageFlag = Bool
f })
| Just Bool
True <- Maybe Bool
e
= SDoc -> SDoc
parens (String -> SDoc
text String
"from" SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
mod))
| Bool
f Bool -> Bool -> Bool
&& GenModule Unit -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName GenModule Unit
mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
m
= SDoc -> SDoc
parens (String -> SDoc
text String
"from" SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
mod))
| (UnitInfo
pkg:[UnitInfo]
_) <- [UnitInfo]
res
= SDoc -> SDoc
parens (String -> SDoc
text String
"from" SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> Unit
mkUnit UnitInfo
pkg)
SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"reexporting" SDoc -> SDoc -> SDoc
<+> GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
mod)
| Bool
f
= SDoc -> SDoc
parens (String -> SDoc
text String
"defined via package flags to be"
SDoc -> SDoc -> SDoc
<+> GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
mod)
| Bool
otherwise = SDoc
Outputable.empty
pp_sugg (SuggestHidden ModuleName
m GenModule Unit
mod ModuleOrigin
o) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
m SDoc -> SDoc -> SDoc
<+> ModuleOrigin -> SDoc
provenance ModuleOrigin
o
where provenance :: ModuleOrigin -> SDoc
provenance ModuleOrigin
ModHidden = SDoc
Outputable.empty
provenance (ModUnusable UnusableUnitReason
_) = SDoc
Outputable.empty
provenance (ModOrigin{ fromOrigUnit :: ModuleOrigin -> Maybe Bool
fromOrigUnit = Maybe Bool
e,
fromHiddenReexport :: ModuleOrigin -> [UnitInfo]
fromHiddenReexport = [UnitInfo]
rhs })
| Just Bool
False <- Maybe Bool
e
= SDoc -> SDoc
parens (String -> SDoc
text String
"needs flag -package-id"
SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
mod))
| (UnitInfo
pkg:[UnitInfo]
_) <- [UnitInfo]
rhs
= SDoc -> SDoc
parens (String -> SDoc
text String
"needs flag -package-id"
SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> Unit
mkUnit UnitInfo
pkg))
| Bool
otherwise = SDoc
Outputable.empty
cantFindInstalledErr :: PtrString -> PtrString -> DynFlags -> ModuleName
-> InstalledFindResult -> SDoc
cantFindInstalledErr :: PtrString
-> PtrString
-> DynFlags
-> ModuleName
-> InstalledFindResult
-> SDoc
cantFindInstalledErr PtrString
cannot_find PtrString
_ DynFlags
dflags ModuleName
mod_name InstalledFindResult
find_result
= PtrString -> SDoc
ptext PtrString
cannot_find SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name)
SDoc -> SDoc -> SDoc
$$ SDoc
more_info
where
more_info :: SDoc
more_info
= case InstalledFindResult
find_result of
InstalledNoPackage UnitId
pkg
-> String -> SDoc
text String
"no unit id matching" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnitId
pkg) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"was found" SDoc -> SDoc -> SDoc
$$ UnitId -> SDoc
looks_like_srcpkgid UnitId
pkg
InstalledNotFound [String]
files Maybe UnitId
mb_pkg
| Just UnitId
pkg <- Maybe UnitId
mb_pkg, Bool -> Bool
not (UnitId
pkg UnitId -> Unit -> Bool
`unitIdEq` DynFlags -> Unit
homeUnit DynFlags
dflags)
-> UnitId -> [String] -> SDoc
forall {a}. Outputable a => a -> [String] -> SDoc
not_found_in_package UnitId
pkg [String]
files
| [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files
-> String -> SDoc
text String
"It is not a module in the current program, or in any known package."
| Bool
otherwise
-> [String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
InstalledFindResult
_ -> String -> SDoc
forall a. String -> a
panic String
"cantFindInstalledErr"
build_tag :: String
build_tag = Set Way -> String
waysBuildTag (DynFlags -> Set Way
ways DynFlags
dflags)
pkgstate :: UnitState
pkgstate = DynFlags -> UnitState
unitState DynFlags
dflags
looks_like_srcpkgid :: UnitId -> SDoc
looks_like_srcpkgid :: UnitId -> SDoc
looks_like_srcpkgid UnitId
pk
| (UnitInfo
pkg:[UnitInfo]
pkgs) <- UnitState -> PackageId -> [UnitInfo]
searchPackageId UnitState
pkgstate (FastString -> PackageId
PackageId (UnitId -> FastString
unitIdFS UnitId
pk))
= SDoc -> SDoc
parens (String -> SDoc
text String
"This unit ID looks like the source package ID;" SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"the real unit ID is" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (FastString -> SDoc
ftext (UnitId -> FastString
unitIdFS (UnitInfo -> UnitId
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
pkg))) SDoc -> SDoc -> SDoc
$$
(if [UnitInfo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
pkgs then SDoc
Outputable.empty
else String -> SDoc
text String
"and" SDoc -> SDoc -> SDoc
<+> Int -> SDoc
int ([UnitInfo] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [UnitInfo]
pkgs) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"other candidates"))
| Bool
otherwise = SDoc
Outputable.empty
not_found_in_package :: a -> [String] -> SDoc
not_found_in_package a
pkg [String]
files
| String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
""
= let
build :: String
build = if String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"p" then String
"profiling"
else String
"\"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
build_tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\""
in
String -> SDoc
text String
"Perhaps you haven't installed the " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
build SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" libraries for package " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg) SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'?' SDoc -> SDoc -> SDoc
$$
[String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
| Bool
otherwise
= String -> SDoc
text String
"There are files missing in the " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" package," SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"try running 'ghc-pkg check'." SDoc -> SDoc -> SDoc
$$
[String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
tried_these :: [FilePath] -> DynFlags -> SDoc
tried_these :: [String] -> DynFlags -> SDoc
tried_these [String]
files DynFlags
dflags
| [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files = SDoc
Outputable.empty
| DynFlags -> Int
verbosity DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
3 =
String -> SDoc
text String
"Use -v (or `:set -v` in ghci) " SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
"to see a list of the files searched for."
| Bool
otherwise =
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Locations searched:") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text [String]
files)