module GHC.Unit.Finder (
FindResult(..),
InstalledFindResult(..),
FinderCache,
flushFinderCaches,
findImportedModule,
findPluginModule,
findExactModule,
findHomeModule,
findExposedPackageModule,
mkHomeModLocation,
mkHomeModLocation2,
mkHiOnlyModLocation,
mkHiPath,
mkObjPath,
addHomeModuleToFinder,
uncacheModule,
mkStubPaths,
findObjectLinkableMaybe,
findObjectLinkable,
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Driver.Env
import GHC.Driver.Session
import GHC.Platform.Ways
import GHC.Builtin.Names ( gHC_PRIM )
import GHC.Unit.Types
import GHC.Unit.Module
import GHC.Unit.Home
import GHC.Unit.State
import GHC.Unit.Finder.Types
import GHC.Data.FastString
import GHC.Data.Maybe ( expectJust )
import qualified GHC.Data.ShortText as ST
import GHC.Utils.Misc
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import GHC.Linker.Types
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 hsc_env =
atomicModifyIORef' fc_ref $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
where
fc_ref = hsc_FC hsc_env
home_unit = hsc_home_unit hsc_env
is_ext mod _ = not (isHomeInstalledModule home_unit mod)
addToFinderCache :: IORef FinderCache -> InstalledModule -> InstalledFindResult -> IO ()
addToFinderCache ref key val =
atomicModifyIORef' ref $ \c -> (extendInstalledModuleEnv c key val, ())
removeFromFinderCache :: IORef FinderCache -> InstalledModule -> IO ()
removeFromFinderCache ref key =
atomicModifyIORef' ref $ \c -> (delInstalledModuleEnv c key, ())
lookupFinderCache :: IORef FinderCache -> InstalledModule -> IO (Maybe InstalledFindResult)
lookupFinderCache ref key = do
c <- readIORef ref
return $! lookupInstalledModuleEnv c key
findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findImportedModule hsc_env mod_name mb_pkg =
case mb_pkg of
Nothing -> unqual_import
Just pkg | pkg == fsLit "this" -> home_import
| otherwise -> pkg_import
where
home_import = findHomeModule hsc_env mod_name
pkg_import = findExposedPackageModule hsc_env mod_name mb_pkg
unqual_import = home_import
`orIfNotFound`
findExposedPackageModule hsc_env mod_name Nothing
findPluginModule :: HscEnv -> ModuleName -> IO FindResult
findPluginModule hsc_env mod_name =
findHomeModule hsc_env mod_name
`orIfNotFound`
findExposedPluginPackageModule hsc_env mod_name
findExactModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
findExactModule hsc_env mod =
let home_unit = hsc_home_unit hsc_env
in if isHomeInstalledModule home_unit mod
then findInstalledHomeModule hsc_env (moduleName mod)
else findPackageModule hsc_env mod
orIfNotFound :: Monad m => m FindResult -> m FindResult -> m FindResult
orIfNotFound this or_this = do
res <- this
case res of
NotFound { fr_paths = paths1, fr_mods_hidden = mh1
, fr_pkgs_hidden = ph1, fr_unusables = u1, fr_suggestions = s1 }
-> do res2 <- or_this
case res2 of
NotFound { fr_paths = paths2, fr_pkg = mb_pkg2, fr_mods_hidden = mh2
, fr_pkgs_hidden = ph2, fr_unusables = u2
, fr_suggestions = s2 }
-> return (NotFound { fr_paths = paths1 ++ paths2
, fr_pkg = mb_pkg2
, fr_mods_hidden = mh1 ++ mh2
, fr_pkgs_hidden = ph1 ++ ph2
, fr_unusables = u1 ++ u2
, fr_suggestions = s1 ++ s2 })
_other -> return res2
_other -> return res
homeSearchCache :: HscEnv -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
homeSearchCache hsc_env mod_name do_this = do
let home_unit = hsc_home_unit hsc_env
mod = mkHomeInstalledModule home_unit mod_name
modLocationCache hsc_env mod do_this
findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
-> IO FindResult
findExposedPackageModule hsc_env mod_name mb_pkg
= findLookupResult hsc_env
$ lookupModuleWithSuggestions
(hsc_units hsc_env) mod_name mb_pkg
findExposedPluginPackageModule :: HscEnv -> ModuleName
-> IO FindResult
findExposedPluginPackageModule hsc_env mod_name
= findLookupResult hsc_env
$ lookupPluginModuleWithSuggestions
(hsc_units hsc_env) mod_name Nothing
findLookupResult :: HscEnv -> LookupResult -> IO FindResult
findLookupResult hsc_env r = case r of
LookupFound m pkg_conf -> do
let im = fst (getModuleInstantiation m)
r' <- findPackageModule_ hsc_env im pkg_conf
case r' of
InstalledFound loc _ -> return (Found loc m)
InstalledNoPackage _ -> return (NoPackage (moduleUnit m))
InstalledNotFound fp _ -> return (NotFound{ fr_paths = fp, fr_pkg = Just (moduleUnit m)
, fr_pkgs_hidden = []
, fr_mods_hidden = []
, fr_unusables = []
, fr_suggestions = []})
LookupMultiple rs ->
return (FoundMultiple rs)
LookupHidden pkg_hiddens mod_hiddens ->
return (NotFound{ fr_paths = [], fr_pkg = Nothing
, fr_pkgs_hidden = map (moduleUnit.fst) pkg_hiddens
, fr_mods_hidden = map (moduleUnit.fst) mod_hiddens
, fr_unusables = []
, fr_suggestions = [] })
LookupUnusable unusable ->
let unusables' = map get_unusable unusable
get_unusable (m, ModUnusable r) = (moduleUnit m, r)
get_unusable (_, r) =
pprPanic "findLookupResult: unexpected origin" (ppr r)
in return (NotFound{ fr_paths = [], fr_pkg = Nothing
, fr_pkgs_hidden = []
, fr_mods_hidden = []
, fr_unusables = unusables'
, fr_suggestions = [] })
LookupNotFound suggest -> do
let suggest'
| gopt Opt_HelpfulErrors (hsc_dflags hsc_env) = suggest
| otherwise = []
return (NotFound{ fr_paths = [], fr_pkg = Nothing
, fr_pkgs_hidden = []
, fr_mods_hidden = []
, fr_unusables = []
, fr_suggestions = suggest' })
modLocationCache :: HscEnv -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
modLocationCache hsc_env mod do_this = do
m <- lookupFinderCache (hsc_FC hsc_env) mod
case m of
Just result -> return result
Nothing -> do
result <- do_this
addToFinderCache (hsc_FC hsc_env) mod result
return result
addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder hsc_env mod_name loc = do
let home_unit = hsc_home_unit hsc_env
mod = mkHomeInstalledModule home_unit mod_name
addToFinderCache (hsc_FC hsc_env) mod (InstalledFound loc mod)
return (mkHomeModule home_unit mod_name)
uncacheModule :: HscEnv -> ModuleName -> IO ()
uncacheModule hsc_env mod_name = do
let home_unit = hsc_home_unit hsc_env
mod = mkHomeInstalledModule home_unit mod_name
removeFromFinderCache (hsc_FC hsc_env) mod
findHomeModule :: HscEnv -> ModuleName -> IO FindResult
findHomeModule hsc_env mod_name = do
r <- findInstalledHomeModule hsc_env mod_name
return $ case r of
InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
InstalledNoPackage _ -> NoPackage uid
InstalledNotFound fps _ -> NotFound {
fr_paths = fps,
fr_pkg = Just uid,
fr_mods_hidden = [],
fr_pkgs_hidden = [],
fr_unusables = [],
fr_suggestions = []
}
where
home_unit = hsc_home_unit hsc_env
uid = homeUnitAsUnit home_unit
findInstalledHomeModule :: HscEnv -> ModuleName -> IO InstalledFindResult
findInstalledHomeModule hsc_env mod_name =
homeSearchCache hsc_env mod_name $
let
dflags = hsc_dflags hsc_env
home_unit = hsc_home_unit hsc_env
home_path = importPaths dflags
hisuf = hiSuf dflags
mod = mkHomeInstalledModule home_unit mod_name
source_exts =
[ ("hs", mkHomeModLocationSearched dflags mod_name "hs")
, ("lhs", mkHomeModLocationSearched dflags mod_name "lhs")
, ("hsig", mkHomeModLocationSearched dflags mod_name "hsig")
, ("lhsig", mkHomeModLocationSearched dflags mod_name "lhsig")
]
hi_exts = [ (hisuf, mkHomeModHiOnlyLocation dflags mod_name)
, (addBootSuffix hisuf, mkHomeModHiOnlyLocation dflags mod_name)
]
exts | isOneShot (ghcMode dflags) = hi_exts
| otherwise = source_exts
in
if mod `installedModuleEq` gHC_PRIM
then return (InstalledFound (error "GHC.Prim ModLocation") mod)
else searchPathExts home_path mod exts
findPackageModule :: HscEnv -> InstalledModule -> IO InstalledFindResult
findPackageModule hsc_env mod = do
let pkg_id = moduleUnit mod
case lookupUnitId (hsc_units hsc_env) pkg_id of
Nothing -> return (InstalledNoPackage pkg_id)
Just u -> findPackageModule_ hsc_env mod u
findPackageModule_ :: HscEnv -> InstalledModule -> UnitInfo -> IO InstalledFindResult
findPackageModule_ hsc_env mod pkg_conf =
ASSERT2( moduleUnit mod == unitId pkg_conf, ppr (moduleUnit mod) <+> ppr (unitId pkg_conf) )
modLocationCache hsc_env mod $
if mod `installedModuleEq` gHC_PRIM
then return (InstalledFound (error "GHC.Prim ModLocation") mod)
else
let
dflags = hsc_dflags hsc_env
tag = waysBuildTag (ways dflags)
package_hisuf | null tag = "hi"
| otherwise = tag ++ "_hi"
mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf
import_dirs = map ST.unpack $ unitImportDirs pkg_conf
in
case import_dirs of
[one] | MkDepend <- ghcMode dflags -> do
let basename = moduleNameSlashes (moduleName mod)
loc <- mk_hi_loc one basename
return (InstalledFound loc mod)
_otherwise ->
searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
searchPathExts :: [FilePath]
-> InstalledModule
-> [ (
FileExt,
FilePath -> BaseName -> IO ModLocation
)
]
-> IO InstalledFindResult
searchPathExts paths mod exts = search to_search
where
basename = moduleNameSlashes (moduleName mod)
to_search :: [(FilePath, IO ModLocation)]
to_search = [ (file, fn path basename)
| path <- paths,
(ext,fn) <- exts,
let base | path == "." = basename
| otherwise = path </> basename
file = base <.> ext
]
search [] = return (InstalledNotFound (map fst to_search) (Just (moduleUnit mod)))
search ((file, mk_result) : rest) = do
b <- doesFileExist file
if b
then do { loc <- mk_result; return (InstalledFound loc mod) }
else search rest
mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt
-> FilePath -> BaseName -> IO ModLocation
mkHomeModLocationSearched dflags mod suff path basename =
mkHomeModLocation2 dflags mod (path </> basename) suff
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
mkHomeModLocation dflags mod src_filename = do
let (basename,extension) = splitExtension src_filename
mkHomeModLocation2 dflags mod basename extension
mkHomeModLocation2 :: DynFlags
-> ModuleName
-> FilePath
-> String
-> IO ModLocation
mkHomeModLocation2 dflags mod src_basename ext = do
let mod_basename = moduleNameSlashes mod
obj_fn = mkObjPath dflags src_basename mod_basename
hi_fn = mkHiPath dflags src_basename mod_basename
hie_fn = mkHiePath dflags src_basename mod_basename
return (ModLocation{ ml_hs_file = Just (src_basename <.> ext),
ml_hi_file = hi_fn,
ml_obj_file = obj_fn,
ml_hie_file = hie_fn })
mkHomeModHiOnlyLocation :: DynFlags
-> ModuleName
-> FilePath
-> BaseName
-> IO ModLocation
mkHomeModHiOnlyLocation dflags mod path basename = do
loc <- mkHomeModLocation2 dflags mod (path </> basename) ""
return loc { ml_hs_file = Nothing }
mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
-> IO ModLocation
mkHiOnlyModLocation dflags hisuf path basename
= do let full_basename = path </> basename
obj_fn = mkObjPath dflags full_basename basename
hie_fn = mkHiePath dflags full_basename basename
return ModLocation{ ml_hs_file = Nothing,
ml_hi_file = full_basename <.> hisuf,
ml_obj_file = obj_fn,
ml_hie_file = hie_fn
}
mkObjPath
:: DynFlags
-> FilePath
-> String
-> FilePath
mkObjPath dflags basename mod_basename = obj_basename <.> osuf
where
odir = objectDir dflags
osuf = objectSuf dflags
obj_basename | Just dir <- odir = dir </> mod_basename
| otherwise = basename
mkHiPath
:: DynFlags
-> FilePath
-> String
-> FilePath
mkHiPath dflags basename mod_basename = hi_basename <.> hisuf
where
hidir = hiDir dflags
hisuf = hiSuf dflags
hi_basename | Just dir <- hidir = dir </> mod_basename
| otherwise = basename
mkHiePath
:: DynFlags
-> FilePath
-> String
-> FilePath
mkHiePath dflags basename mod_basename = hie_basename <.> hiesuf
where
hiedir = hieDir dflags
hiesuf = hieSuf dflags
hie_basename | Just dir <- hiedir = dir </> mod_basename
| otherwise = basename
mkStubPaths
:: DynFlags
-> ModuleName
-> ModLocation
-> FilePath
mkStubPaths dflags mod location
= let
stubdir = stubDir dflags
mod_basename = moduleNameSlashes mod
src_basename = dropExtension $ expectJust "mkStubPaths"
(ml_hs_file location)
stub_basename0
| Just dir <- stubdir = dir </> mod_basename
| otherwise = src_basename
stub_basename = stub_basename0 ++ "_stub"
in
stub_basename <.> "h"
findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
findObjectLinkableMaybe mod locn
= do let obj_fn = ml_obj_file locn
maybe_obj_time <- modificationTimeIfExists obj_fn
case maybe_obj_time of
Nothing -> return Nothing
Just obj_time -> liftM Just (findObjectLinkable mod obj_fn obj_time)
findObjectLinkable :: Module -> FilePath -> UTCTime -> IO Linkable
findObjectLinkable mod obj_fn obj_time = return (LM obj_time mod [DotO obj_fn])