module Finder (
flushFinderCaches,
FindResult(..),
findImportedModule,
findExactModule,
findHomeModule,
findExposedPackageModule,
mkHomeModLocation,
mkHomeModLocation2,
mkHiOnlyModLocation,
addHomeModuleToFinder,
uncacheModule,
mkStubPaths,
findObjectLinkableMaybe,
findObjectLinkable,
cannotFindModule,
cannotFindInterface,
) where
#include "HsVersions.h"
import Module
import HscTypes
import Packages
import FastString
import Util
import PrelNames ( gHC_PRIM )
import DynFlags
import Outputable
import UniqFM
import Maybes ( expectJust )
import Exception ( evaluate )
import Data.IORef ( IORef, writeIORef, readIORef, atomicModifyIORef )
import System.Directory
import System.FilePath
import Control.Monad
import Data.Time
import Data.List ( foldl' )
type FileExt = String
type BaseName = String
flushFinderCaches :: HscEnv -> IO ()
flushFinderCaches hsc_env = do
writeIORef fc_ref emptyUFM
flushModLocationCache this_pkg mlc_ref
where
this_pkg = thisPackage (hsc_dflags hsc_env)
fc_ref = hsc_FC hsc_env
mlc_ref = hsc_MLC hsc_env
flushModLocationCache :: PackageKey -> IORef ModLocationCache -> IO ()
flushModLocationCache this_pkg ref = do
atomicModifyIORef ref $ \fm -> (filterModuleEnv is_ext fm, ())
_ <- evaluate =<< readIORef ref
return ()
where is_ext mod _ | modulePackageKey mod /= this_pkg = True
| otherwise = False
addToFinderCache :: IORef FinderCache -> ModuleName -> FindResult -> IO ()
addToFinderCache ref key val =
atomicModifyIORef ref $ \c -> (addToUFM c key val, ())
addToModLocationCache :: IORef ModLocationCache -> Module -> ModLocation -> IO ()
addToModLocationCache ref key val =
atomicModifyIORef ref $ \c -> (extendModuleEnv c key val, ())
removeFromFinderCache :: IORef FinderCache -> ModuleName -> IO ()
removeFromFinderCache ref key =
atomicModifyIORef ref $ \c -> (delFromUFM c key, ())
removeFromModLocationCache :: IORef ModLocationCache -> Module -> IO ()
removeFromModLocationCache ref key =
atomicModifyIORef ref $ \c -> (delModuleEnv c key, ())
lookupFinderCache :: IORef FinderCache -> ModuleName -> IO (Maybe FindResult)
lookupFinderCache ref key = do
c <- readIORef ref
return $! lookupUFM c key
lookupModLocationCache :: IORef ModLocationCache -> Module
-> IO (Maybe ModLocation)
lookupModLocationCache ref key = do
c <- readIORef ref
return $! lookupModuleEnv 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
findExactModule :: HscEnv -> Module -> IO FindResult
findExactModule hsc_env mod =
let dflags = hsc_dflags hsc_env
in if modulePackageKey mod == thisPackage dflags
then findHomeModule hsc_env (moduleName mod)
else findPackageModule hsc_env mod
orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult
orIfNotFound this or_this = do
res <- this
case res of
NotFound { fr_paths = paths1, fr_mods_hidden = mh1
, fr_pkgs_hidden = ph1, 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_suggestions = s2 }
-> return (NotFound { fr_paths = paths1 ++ paths2
, fr_pkg = mb_pkg2
, fr_mods_hidden = mh1 ++ mh2
, fr_pkgs_hidden = ph1 ++ ph2
, fr_suggestions = s1 ++ s2 })
_other -> return res2
_other -> return res
homeSearchCache :: HscEnv -> ModuleName -> IO FindResult -> IO FindResult
homeSearchCache hsc_env mod_name do_this = do
m <- lookupFinderCache (hsc_FC hsc_env) mod_name
case m of
Just result -> return result
Nothing -> do
result <- do_this
addToFinderCache (hsc_FC hsc_env) mod_name result
case result of
Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc
_other -> return ()
return result
findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
-> IO FindResult
findExposedPackageModule hsc_env mod_name mb_pkg
= case lookupModuleWithSuggestions (hsc_dflags hsc_env) mod_name mb_pkg of
LookupFound m pkg_conf ->
findPackageModule_ hsc_env m pkg_conf
LookupMultiple rs ->
return (FoundMultiple rs)
LookupHidden pkg_hiddens mod_hiddens ->
return (NotFound{ fr_paths = [], fr_pkg = Nothing
, fr_pkgs_hidden = map (modulePackageKey.fst) pkg_hiddens
, fr_mods_hidden = map (modulePackageKey.fst) mod_hiddens
, fr_suggestions = [] })
LookupNotFound suggest ->
return (NotFound{ fr_paths = [], fr_pkg = Nothing
, fr_pkgs_hidden = []
, fr_mods_hidden = []
, fr_suggestions = suggest })
modLocationCache :: HscEnv -> Module -> IO FindResult -> IO FindResult
modLocationCache hsc_env mod do_this = do
mb_loc <- lookupModLocationCache mlc mod
case mb_loc of
Just loc -> return (Found loc mod)
Nothing -> do
result <- do_this
case result of
Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc
_other -> return ()
return result
where
mlc = hsc_MLC hsc_env
addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder hsc_env mod_name loc = do
let mod = mkModule (thisPackage (hsc_dflags hsc_env)) mod_name
addToFinderCache (hsc_FC hsc_env) mod_name (Found loc mod)
addToModLocationCache (hsc_MLC hsc_env) mod loc
return mod
uncacheModule :: HscEnv -> ModuleName -> IO ()
uncacheModule hsc_env mod = do
let this_pkg = thisPackage (hsc_dflags hsc_env)
removeFromFinderCache (hsc_FC hsc_env) mod
removeFromModLocationCache (hsc_MLC hsc_env) (mkModule this_pkg mod)
findHomeModule :: HscEnv -> ModuleName -> IO FindResult
findHomeModule hsc_env mod_name =
homeSearchCache hsc_env mod_name $
let
dflags = hsc_dflags hsc_env
home_path = importPaths dflags
hisuf = hiSuf dflags
mod = mkModule (thisPackage dflags) 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, mkHiOnlyModLocation dflags hisuf)
, (addBootSuffix hisuf, mkHiOnlyModLocation dflags hisuf)
]
exts | isOneShot (ghcMode dflags) = hi_exts
| otherwise = source_exts
in
if mod == gHC_PRIM
then return (Found (error "GHC.Prim ModLocation") mod)
else searchPathExts home_path mod exts
findPackageModule :: HscEnv -> Module -> IO FindResult
findPackageModule hsc_env mod = do
let
dflags = hsc_dflags hsc_env
pkg_id = modulePackageKey mod
case lookupPackage dflags pkg_id of
Nothing -> return (NoPackage pkg_id)
Just pkg_conf -> findPackageModule_ hsc_env mod pkg_conf
findPackageModule_ :: HscEnv -> Module -> PackageConfig -> IO FindResult
findPackageModule_ hsc_env mod pkg_conf =
ASSERT( modulePackageKey mod == packageConfigId pkg_conf )
modLocationCache hsc_env mod $
if mod == gHC_PRIM
then return (Found (error "GHC.Prim ModLocation") mod)
else
let
dflags = hsc_dflags hsc_env
tag = buildTag dflags
package_hisuf | null tag = "hi"
| otherwise = tag ++ "_hi"
mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf
import_dirs = importDirs pkg_conf
in
case import_dirs of
[one] | MkDepend <- ghcMode dflags -> do
let basename = moduleNameSlashes (moduleName mod)
loc <- mk_hi_loc one basename
return (Found loc mod)
_otherwise ->
searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
searchPathExts
:: [FilePath]
-> Module
-> [ (
FileExt,
FilePath -> BaseName -> IO ModLocation
)
]
-> IO FindResult
searchPathExts paths mod exts
= do result <- search to_search
return result
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 (NotFound { fr_paths = map fst to_search
, fr_pkg = Just (modulePackageKey mod)
, fr_mods_hidden = [], fr_pkgs_hidden = []
, fr_suggestions = [] })
search ((file, mk_result) : rest) = do
b <- doesFileExist file
if b
then do { loc <- mk_result; return (Found loc mod) }
else search rest
mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt
-> FilePath -> BaseName -> IO ModLocation
mkHomeModLocationSearched dflags mod suff path basename = do
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
return (ModLocation{ ml_hs_file = Just (src_basename <.> ext),
ml_hi_file = hi_fn,
ml_obj_file = obj_fn })
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
return ModLocation{ ml_hs_file = Nothing,
ml_hi_file = full_basename <.> hisuf,
ml_obj_file = obj_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
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])
cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
cannotFindModule = cantFindErr (sLit "Could not find module")
(sLit "Ambiguous module name")
cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc
cannotFindInterface = cantFindErr (sLit "Failed to load interface for")
(sLit "Ambiguous interface for")
cantFindErr :: LitString -> LitString -> DynFlags -> ModuleName -> FindResult
-> SDoc
cantFindErr _ multiple_found _ mod_name (FoundMultiple mods)
| Just pkgs <- unambiguousPackages
= hang (ptext multiple_found <+> quotes (ppr mod_name) <> colon) 2 (
sep [ptext (sLit "it was found in multiple packages:"),
hsep (map ppr pkgs) ]
)
| otherwise
= hang (ptext multiple_found <+> quotes (ppr mod_name) <> colon) 2 (
vcat (map pprMod mods)
)
where
unambiguousPackages = foldl' unambiguousPackage (Just []) mods
unambiguousPackage (Just xs) (m, ModOrigin (Just _) _ _ _)
= Just (modulePackageKey m : xs)
unambiguousPackage _ _ = Nothing
pprMod (m, o) = ptext (sLit "it is bound as") <+> ppr m <+>
ptext (sLit "by") <+> pprOrigin m o
pprOrigin _ ModHidden = panic "cantFindErr: bound by mod hidden"
pprOrigin m (ModOrigin e res _ f) = sep $ punctuate comma (
if e == Just True
then [ptext (sLit "package") <+> ppr (modulePackageKey m)]
else [] ++
map ((ptext (sLit "a reexport in package") <+>)
.ppr.packageConfigId) res ++
if f then [ptext (sLit "a package flag")] else []
)
cantFindErr cannot_find _ dflags mod_name find_result
= ptext cannot_find <+> quotes (ppr mod_name)
$$ more_info
where
more_info
= case find_result of
NoPackage pkg
-> ptext (sLit "no package key matching") <+> quotes (ppr pkg) <+>
ptext (sLit "was found") $$ looks_like_srcpkgid pkg
NotFound { fr_paths = files, fr_pkg = mb_pkg
, fr_mods_hidden = mod_hiddens, fr_pkgs_hidden = pkg_hiddens
, fr_suggestions = suggest }
| Just pkg <- mb_pkg, pkg /= thisPackage dflags
-> not_found_in_package pkg files
| not (null suggest)
-> pp_suggestions suggest $$ tried_these files
| null files && null mod_hiddens && null pkg_hiddens
-> ptext (sLit "It is not a module in the current program, or in any known package.")
| otherwise
-> vcat (map pkg_hidden pkg_hiddens) $$
vcat (map mod_hidden mod_hiddens) $$
tried_these files
_ -> panic "cantFindErr"
build_tag = buildTag dflags
not_found_in_package pkg files
| build_tag /= ""
= let
build = if build_tag == "p" then "profiling"
else "\"" ++ build_tag ++ "\""
in
ptext (sLit "Perhaps you haven't installed the ") <> text build <>
ptext (sLit " libraries for package ") <> quotes (ppr pkg) <> char '?' $$
tried_these files
| otherwise
= ptext (sLit "There are files missing in the ") <> quotes (ppr pkg) <>
ptext (sLit " package,") $$
ptext (sLit "try running 'ghc-pkg check'.") $$
tried_these files
tried_these files
| null files = Outputable.empty
| verbosity dflags < 3 =
ptext (sLit "Use -v to see a list of the files searched for.")
| otherwise =
hang (ptext (sLit "Locations searched:")) 2 $ vcat (map text files)
pkg_hidden :: PackageKey -> SDoc
pkg_hidden pkgid =
ptext (sLit "It is a member of the hidden package")
<+> quotes (ppr pkgid)
<> dot $$ cabal_pkg_hidden_hint pkgid
cabal_pkg_hidden_hint pkgid
| gopt Opt_BuildingCabalPackage dflags
= let pkg = expectJust "pkg_hidden" (lookupPackage dflags pkgid)
in ptext (sLit "Perhaps you need to add") <+>
quotes (ppr (packageName pkg)) <+>
ptext (sLit "to the build-depends in your .cabal file.")
| otherwise = Outputable.empty
looks_like_srcpkgid :: PackageKey -> SDoc
looks_like_srcpkgid pk
| (pkg:pkgs) <- searchPackageId dflags (SourcePackageId (packageKeyFS pk))
= parens (text "This package key looks like the source package ID;" $$
text "the real package key is" <+> quotes (ftext (packageKeyFS (packageKey pkg))) $$
(if null pkgs then Outputable.empty
else text "and" <+> int (length pkgs) <+> text "other candidates"))
| otherwise = Outputable.empty
mod_hidden pkg =
ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg)
pp_suggestions :: [ModuleSuggestion] -> SDoc
pp_suggestions sugs
| null sugs = Outputable.empty
| otherwise = hang (ptext (sLit "Perhaps you meant"))
2 (vcat (map pp_sugg sugs))
pp_sugg (SuggestVisible m mod o) = ppr m <+> provenance o
where provenance ModHidden = Outputable.empty
provenance (ModOrigin{ fromOrigPackage = e,
fromExposedReexport = res,
fromPackageFlag = f })
| Just True <- e
= parens (ptext (sLit "from") <+> ppr (modulePackageKey mod))
| f && moduleName mod == m
= parens (ptext (sLit "from") <+> ppr (modulePackageKey mod))
| (pkg:_) <- res
= parens (ptext (sLit "from") <+> ppr (packageConfigId pkg)
<> comma <+> ptext (sLit "reexporting") <+> ppr mod)
| f
= parens (ptext (sLit "defined via package flags to be")
<+> ppr mod)
| otherwise = Outputable.empty
pp_sugg (SuggestHidden m mod o) = ppr m <+> provenance o
where provenance ModHidden = Outputable.empty
provenance (ModOrigin{ fromOrigPackage = e,
fromHiddenReexport = rhs })
| Just False <- e
= parens (ptext (sLit "needs flag -package-key")
<+> ppr (modulePackageKey mod))
| (pkg:_) <- rhs
= parens (ptext (sLit "needs flag -package-key")
<+> ppr (packageConfigId pkg))
| otherwise = Outputable.empty