module GHC.Runtime.Linker
( getHValue
, showLinkerState
, linkExpr
, linkDecls
, unload
, withExtendedLinkEnv
, extendLinkEnv
, deleteFromLinkEnv
, extendLoadedPkgs
, linkPackages
, initDynLinker
, linkModule
, linkCmdLineLibs
, uninitializedLinker
)
where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Runtime.Interpreter
import GHC.Runtime.Interpreter.Types
import GHCi.RemoteTypes
import GHC.Iface.Load
import GHC.ByteCode.Linker
import GHC.ByteCode.Asm
import GHC.ByteCode.Types
import GHC.Tc.Utils.Monad
import GHC.Unit.State as Packages
import GHC.Driver.Phases
import GHC.Driver.Finder
import GHC.Driver.Types
import GHC.Driver.Ways
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Unit.Module
import GHC.Data.List.SetOps
import GHC.Runtime.Linker.Types (DynLinker(..), PersistentLinkerState(..))
import GHC.Driver.Session
import GHC.Types.Basic
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Misc
import GHC.Utils.Error
import GHC.Types.SrcLoc
import qualified GHC.Data.Maybe as Maybes
import GHC.Types.Unique.DSet
import GHC.Data.FastString
import GHC.Platform
import GHC.SysTools
import GHC.SysTools.FileCleanup
import Control.Monad
import qualified Data.Set as Set
import Data.Char (isSpace)
import Data.Function ((&))
import Data.IORef
import Data.List (intercalate, isPrefixOf, isSuffixOf, nub, partition)
import Data.Maybe
import Control.Concurrent.MVar
import qualified Control.Monad.Catch as MC
import System.FilePath
import System.Directory
import System.IO.Unsafe
import System.Environment (lookupEnv)
#if defined(mingw32_HOST_OS)
import System.Win32.Info (getSystemDirectory)
#endif
import GHC.Utils.Exception
uninitializedLinker :: IO DynLinker
uninitializedLinker =
newMVar Nothing >>= (pure . DynLinker)
uninitialised :: a
uninitialised = panic "Dynamic linker not initialised"
modifyPLS_ :: DynLinker -> (PersistentLinkerState -> IO PersistentLinkerState) -> IO ()
modifyPLS_ dl f =
modifyMVar_ (dl_mpls dl) (fmap pure . f . fromMaybe uninitialised)
modifyPLS :: DynLinker -> (PersistentLinkerState -> IO (PersistentLinkerState, a)) -> IO a
modifyPLS dl f =
modifyMVar (dl_mpls dl) (fmapFst pure . f . fromMaybe uninitialised)
where fmapFst f = fmap (\(x, y) -> (f x, y))
readPLS :: DynLinker -> IO PersistentLinkerState
readPLS dl =
(fmap (fromMaybe uninitialised) . readMVar) (dl_mpls dl)
modifyMbPLS_
:: DynLinker -> (Maybe PersistentLinkerState -> IO (Maybe PersistentLinkerState)) -> IO ()
modifyMbPLS_ dl f = modifyMVar_ (dl_mpls dl) f
emptyPLS :: PersistentLinkerState
emptyPLS = PersistentLinkerState
{ closure_env = emptyNameEnv
, itbl_env = emptyNameEnv
, pkgs_loaded = init_pkgs
, bcos_loaded = []
, objs_loaded = []
, temp_sos = []
}
where init_pkgs = [rtsUnitId]
extendLoadedPkgs :: DynLinker -> [UnitId] -> IO ()
extendLoadedPkgs dl pkgs =
modifyPLS_ dl $ \s ->
return s{ pkgs_loaded = pkgs ++ pkgs_loaded s }
extendLinkEnv :: DynLinker -> [(Name,ForeignHValue)] -> IO ()
extendLinkEnv dl new_bindings =
modifyPLS_ dl $ \pls@PersistentLinkerState{..} -> do
let new_ce = extendClosureEnv closure_env new_bindings
return $! pls{ closure_env = new_ce }
deleteFromLinkEnv :: DynLinker -> [Name] -> IO ()
deleteFromLinkEnv dl to_remove =
modifyPLS_ dl $ \pls -> do
let ce = closure_env pls
let new_ce = delListFromNameEnv ce to_remove
return pls{ closure_env = new_ce }
getHValue :: HscEnv -> Name -> IO ForeignHValue
getHValue hsc_env name = do
let dl = hsc_dynLinker hsc_env
initDynLinker hsc_env
pls <- modifyPLS dl $ \pls -> do
if (isExternalName name) then do
(pls', ok) <- linkDependencies hsc_env pls noSrcSpan
[nameModule name]
if (failed ok) then throwGhcExceptionIO (ProgramError "")
else return (pls', pls')
else
return (pls, pls)
case lookupNameEnv (closure_env pls) name of
Just (_,aa) -> return aa
Nothing
-> ASSERT2(isExternalName name, ppr name)
do let sym_to_find = nameToCLabel name "closure"
m <- lookupClosure hsc_env (unpackFS sym_to_find)
case m of
Just hvref -> mkFinalizedHValue hsc_env hvref
Nothing -> linkFail "GHC.Runtime.Linker.getHValue"
(unpackFS sym_to_find)
linkDependencies :: HscEnv -> PersistentLinkerState
-> SrcSpan -> [Module]
-> IO (PersistentLinkerState, SuccessFlag)
linkDependencies hsc_env pls span needed_mods = do
let hpt = hsc_HPT hsc_env
maybe_normal_osuf <- checkNonStdWay hsc_env span
(lnks, pkgs) <- getLinkDeps hsc_env hpt pls
maybe_normal_osuf span needed_mods
pls1 <- linkPackages' hsc_env pkgs pls
linkModules hsc_env pls1 lnks
withExtendedLinkEnv :: (ExceptionMonad m) =>
DynLinker -> [(Name,ForeignHValue)] -> m a -> m a
withExtendedLinkEnv dl new_env action
= MC.bracket (liftIO $ extendLinkEnv dl new_env)
(\_ -> reset_old_env)
(\_ -> action)
where
reset_old_env = liftIO $ do
modifyPLS_ dl $ \pls ->
let cur = closure_env pls
new = delListFromNameEnv cur (map fst new_env)
in return pls{ closure_env = new }
showLinkerState :: DynLinker -> IO SDoc
showLinkerState dl
= do pls <- readPLS dl
return $ withPprStyle defaultDumpStyle
(vcat [text "----- Linker state -----",
text "Pkgs:" <+> ppr (pkgs_loaded pls),
text "Objs:" <+> ppr (objs_loaded pls),
text "BCOs:" <+> ppr (bcos_loaded pls)])
initDynLinker :: HscEnv -> IO ()
initDynLinker hsc_env = do
let dl = hsc_dynLinker hsc_env
modifyMbPLS_ dl $ \pls -> do
case pls of
Just _ -> return pls
Nothing -> Just <$> reallyInitDynLinker hsc_env
reallyInitDynLinker :: HscEnv -> IO PersistentLinkerState
reallyInitDynLinker hsc_env = do
let dflags = hsc_dflags hsc_env
pls0 = emptyPLS
initObjLinker hsc_env
pls <- linkPackages' hsc_env (preloadUnits (unitState dflags)) pls0
linkCmdLineLibs' hsc_env pls
linkCmdLineLibs :: HscEnv -> IO ()
linkCmdLineLibs hsc_env = do
let dl = hsc_dynLinker hsc_env
initDynLinker hsc_env
modifyPLS_ dl $ \pls -> do
linkCmdLineLibs' hsc_env pls
linkCmdLineLibs' :: HscEnv -> PersistentLinkerState -> IO PersistentLinkerState
linkCmdLineLibs' hsc_env pls =
do
let dflags@(DynFlags { ldInputs = cmdline_ld_inputs
, libraryPaths = lib_paths_base})
= hsc_dflags hsc_env
let minus_ls_1 = [ lib | Option ('-':'l':lib) <- cmdline_ld_inputs ]
let platform = targetPlatform dflags
os = platformOS platform
minus_ls = case os of
OSMinGW32 -> "pthread" : minus_ls_1
_ -> minus_ls_1
gcc_paths <- getGCCPaths dflags os
lib_paths_env <- addEnvPaths "LIBRARY_PATH" lib_paths_base
maybePutStrLn dflags "Search directories (user):"
maybePutStr dflags (unlines $ map (" "++) lib_paths_env)
maybePutStrLn dflags "Search directories (gcc):"
maybePutStr dflags (unlines $ map (" "++) gcc_paths)
libspecs
<- mapM (locateLib hsc_env False lib_paths_env gcc_paths) minus_ls
classified_ld_inputs <- mapM (classifyLdInput dflags)
[ f | FileOption _ f <- cmdline_ld_inputs ]
let platform = targetPlatform dflags
let (framework_paths, frameworks) =
if platformUsesFrameworks platform
then (frameworkPaths dflags, cmdlineFrameworks dflags)
else ([],[])
let cmdline_lib_specs = catMaybes classified_ld_inputs
++ libspecs
++ map Framework frameworks
if null cmdline_lib_specs then return pls
else do
let all_paths = let paths = takeDirectory (pgm_c dflags)
: framework_paths
++ lib_paths_base
++ [ takeDirectory dll | DLLPath dll <- libspecs ]
in nub $ map normalise paths
let lib_paths = nub $ lib_paths_base ++ gcc_paths
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath hsc_env) all_paths_env
let merged_specs = mergeStaticObjects cmdline_lib_specs
pls1 <- foldM (preloadLib hsc_env lib_paths framework_paths) pls
merged_specs
maybePutStr dflags "final link ... "
ok <- resolveObjs hsc_env
mapM_ (removeLibrarySearchPath hsc_env) $ reverse pathCache
if succeeded ok then maybePutStrLn dflags "done"
else throwGhcExceptionIO (ProgramError "linking extra libraries/objects failed")
return pls1
mergeStaticObjects :: [LibrarySpec] -> [LibrarySpec]
mergeStaticObjects specs = go [] specs
where
go :: [FilePath] -> [LibrarySpec] -> [LibrarySpec]
go accum (Objects objs : rest) = go (objs ++ accum) rest
go accum@(_:_) rest = Objects (reverse accum) : go [] rest
go [] (spec:rest) = spec : go [] rest
go [] [] = []
classifyLdInput :: DynFlags -> FilePath -> IO (Maybe LibrarySpec)
classifyLdInput dflags f
| isObjectFilename platform f = return (Just (Objects [f]))
| isDynLibFilename platform f = return (Just (DLLPath f))
| otherwise = do
putLogMsg dflags NoReason SevInfo noSrcSpan
$ withPprStyle defaultUserStyle
(text ("Warning: ignoring unrecognised input `" ++ f ++ "'"))
return Nothing
where platform = targetPlatform dflags
preloadLib
:: HscEnv -> [String] -> [String] -> PersistentLinkerState
-> LibrarySpec -> IO PersistentLinkerState
preloadLib hsc_env lib_paths framework_paths pls lib_spec = do
maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ")
case lib_spec of
Objects static_ishs -> do
(b, pls1) <- preload_statics lib_paths static_ishs
maybePutStrLn dflags (if b then "done" else "not found")
return pls1
Archive static_ish -> do
b <- preload_static_archive lib_paths static_ish
maybePutStrLn dflags (if b then "done" else "not found")
return pls
DLL dll_unadorned -> do
maybe_errstr <- loadDLL hsc_env (mkSOName platform dll_unadorned)
case maybe_errstr of
Nothing -> maybePutStrLn dflags "done"
Just mm | platformOS platform /= OSDarwin ->
preloadFailed mm lib_paths lib_spec
Just mm | otherwise -> do
let libfile = ("lib" ++ dll_unadorned) <.> "so"
err2 <- loadDLL hsc_env libfile
case err2 of
Nothing -> maybePutStrLn dflags "done"
Just _ -> preloadFailed mm lib_paths lib_spec
return pls
DLLPath dll_path -> do
do maybe_errstr <- loadDLL hsc_env dll_path
case maybe_errstr of
Nothing -> maybePutStrLn dflags "done"
Just mm -> preloadFailed mm lib_paths lib_spec
return pls
Framework framework ->
if platformUsesFrameworks (targetPlatform dflags)
then do maybe_errstr <- loadFramework hsc_env framework_paths framework
case maybe_errstr of
Nothing -> maybePutStrLn dflags "done"
Just mm -> preloadFailed mm framework_paths lib_spec
return pls
else throwGhcExceptionIO (ProgramError "preloadLib Framework")
where
dflags = hsc_dflags hsc_env
platform = targetPlatform dflags
preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
preloadFailed sys_errmsg paths spec
= do maybePutStr dflags "failed.\n"
throwGhcExceptionIO $
CmdLineError (
"user specified .o/.so/.DLL could not be loaded ("
++ sys_errmsg ++ ")\nWhilst trying to load: "
++ showLS spec ++ "\nAdditional directories searched:"
++ (if null paths then " (none)" else
intercalate "\n" (map (" "++) paths)))
preload_statics _paths names
= do b <- or <$> mapM doesFileExist names
if not b then return (False, pls)
else if hostIsDynamic
then do pls1 <- dynLoadObjs hsc_env pls names
return (True, pls1)
else do mapM_ (loadObj hsc_env) names
return (True, pls)
preload_static_archive _paths name
= do b <- doesFileExist name
if not b then return False
else do if hostIsDynamic
then throwGhcExceptionIO $
CmdLineError dynamic_msg
else loadArchive hsc_env name
return True
where
dynamic_msg = unlines
[ "User-specified static library could not be loaded ("
++ name ++ ")"
, "Loading static libraries is not supported in this configuration."
, "Try using a dynamic library instead."
]
linkExpr :: HscEnv -> SrcSpan -> UnlinkedBCO -> IO ForeignHValue
linkExpr hsc_env span root_ul_bco
= do {
; initDynLinker hsc_env
; let dl = hsc_dynLinker hsc_env
; modifyPLS dl $ \pls0 -> do {
; (pls, ok) <- linkDependencies hsc_env pls0 span needed_mods
; if failed ok then
throwGhcExceptionIO (ProgramError "")
else do {
let ie = itbl_env pls
ce = closure_env pls
; let nobreakarray = error "no break array"
bco_ix = mkNameEnv [(unlinkedBCOName root_ul_bco, 0)]
; resolved <- linkBCO hsc_env ie ce bco_ix nobreakarray root_ul_bco
; [root_hvref] <- createBCOs hsc_env [resolved]
; fhv <- mkFinalizedHValue hsc_env root_hvref
; return (pls, fhv)
}}}
where
free_names = uniqDSetToList (bcoFreeNames root_ul_bco)
needed_mods :: [Module]
needed_mods = [ nameModule n | n <- free_names,
isExternalName n,
not (isWiredInName n)
]
dieWith :: DynFlags -> SrcSpan -> MsgDoc -> IO a
dieWith dflags span msg = throwGhcExceptionIO (ProgramError (showSDoc dflags (mkLocMessage SevFatal span msg)))
checkNonStdWay :: HscEnv -> SrcSpan -> IO (Maybe FilePath)
checkNonStdWay hsc_env srcspan
| Just (ExternalInterp {}) <- hsc_interp hsc_env = return Nothing
| hostFullWays == targetFullWays = return Nothing
| objectSuf (hsc_dflags hsc_env) == normalObjectSuffix && not (null targetFullWays)
= failNonStd (hsc_dflags hsc_env) srcspan
| otherwise = return (Just (hostWayTag ++ "o"))
where
targetFullWays = Set.filter (not . wayRTSOnly) (ways (hsc_dflags hsc_env))
hostWayTag = case waysTag hostFullWays of
"" -> ""
tag -> tag ++ "_"
normalObjectSuffix :: String
normalObjectSuffix = phaseInputExt StopLn
failNonStd :: DynFlags -> SrcSpan -> IO (Maybe FilePath)
failNonStd dflags srcspan = dieWith dflags srcspan $
text "Cannot load" <+> compWay <+>
text "objects when GHC is built" <+> ghciWay $$
text "To fix this, either:" $$
text " (1) Use -fexternal-interpreter, or" $$
text " (2) Build the program twice: once" <+>
ghciWay <> text ", and then" $$
text " with" <+> compWay <+>
text "using -osuf to set a different object file suffix."
where compWay
| WayDyn `elem` ways dflags = text "-dynamic"
| WayProf `elem` ways dflags = text "-prof"
| otherwise = text "normal"
ghciWay
| hostIsDynamic = text "with -dynamic"
| hostIsProfiled = text "with -prof"
| otherwise = text "the normal way"
getLinkDeps :: HscEnv -> HomePackageTable
-> PersistentLinkerState
-> Maybe FilePath
-> SrcSpan
-> [Module]
-> IO ([Linkable], [UnitId])
getLinkDeps hsc_env hpt pls replace_osuf span mods
= do {
; (mods_s, pkgs_s) <- follow_deps (filterOut isInteractiveModule mods)
emptyUniqDSet emptyUniqDSet;
; let {
mods_needed = mods_s `minusList` linked_mods ;
pkgs_needed = pkgs_s `minusList` pkgs_loaded pls ;
linked_mods = map (moduleName.linkableModule)
(objs_loaded pls ++ bcos_loaded pls) }
; let { osuf = objectSuf dflags }
; lnks_needed <- mapM (get_linkable osuf) mods_needed
; return (lnks_needed, pkgs_needed) }
where
dflags = hsc_dflags hsc_env
this_pkg = homeUnit dflags
follow_deps :: [Module]
-> UniqDSet ModuleName
-> UniqDSet UnitId
-> IO ([ModuleName], [UnitId])
follow_deps [] acc_mods acc_pkgs
= return (uniqDSetToList acc_mods, uniqDSetToList acc_pkgs)
follow_deps (mod:mods) acc_mods acc_pkgs
= do
mb_iface <- initIfaceCheck (text "getLinkDeps") hsc_env $
loadInterface msg mod (ImportByUser NotBoot)
iface <- case mb_iface of
Maybes.Failed err -> throwGhcExceptionIO (ProgramError (showSDoc dflags err))
Maybes.Succeeded iface -> return iface
when (mi_boot iface == IsBoot) $ link_boot_mod_error mod
let
pkg = moduleUnit mod
deps = mi_deps iface
pkg_deps = dep_pkgs deps
(boot_deps, mod_deps) = flip partitionWith (dep_mods deps) $
\ (GWIB { gwib_mod = m, gwib_isBoot = is_boot }) ->
m & case is_boot of
IsBoot -> Left
NotBoot -> Right
boot_deps' = filter (not . (`elementOfUniqDSet` acc_mods)) boot_deps
acc_mods' = addListToUniqDSet acc_mods (moduleName mod : mod_deps)
acc_pkgs' = addListToUniqDSet acc_pkgs $ map fst pkg_deps
if pkg /= this_pkg
then follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg))
else follow_deps (map (mkModule this_pkg) boot_deps' ++ mods)
acc_mods' acc_pkgs'
where
msg = text "need to link module" <+> ppr mod <+>
text "due to use of Template Haskell"
link_boot_mod_error mod =
throwGhcExceptionIO (ProgramError (showSDoc dflags (
text "module" <+> ppr mod <+>
text "cannot be linked; it is only available as a boot module")))
no_obj :: Outputable a => a -> IO b
no_obj mod = dieWith dflags span $
text "cannot find object file for module " <>
quotes (ppr mod) $$
while_linking_expr
while_linking_expr = text "while linking an interpreted expression"
get_linkable osuf mod_name
| Just mod_info <- lookupHpt hpt mod_name
= adjust_linkable (Maybes.expectJust "getLinkDeps" (hm_linkable mod_info))
| otherwise
= do
mb_stuff <- findHomeModule hsc_env mod_name
case mb_stuff of
Found loc mod -> found loc mod
_ -> no_obj mod_name
where
found loc mod = do {
mb_lnk <- findObjectLinkableMaybe mod loc ;
case mb_lnk of {
Nothing -> no_obj mod ;
Just lnk -> adjust_linkable lnk
}}
adjust_linkable lnk
| Just new_osuf <- replace_osuf = do
new_uls <- mapM (adjust_ul new_osuf)
(linkableUnlinked lnk)
return lnk{ linkableUnlinked=new_uls }
| otherwise =
return lnk
adjust_ul new_osuf (DotO file) = do
MASSERT(osuf `isSuffixOf` file)
let file_base = fromJust (stripExtension osuf file)
new_file = file_base <.> new_osuf
ok <- doesFileExist new_file
if (not ok)
then dieWith dflags span $
text "cannot find object file "
<> quotes (text new_file) $$ while_linking_expr
else return (DotO new_file)
adjust_ul _ (DotA fp) = panic ("adjust_ul DotA " ++ show fp)
adjust_ul _ (DotDLL fp) = panic ("adjust_ul DotDLL " ++ show fp)
adjust_ul _ l@(BCOs {}) = return l
linkDecls :: HscEnv -> SrcSpan -> CompiledByteCode -> IO ()
linkDecls hsc_env span cbc@CompiledByteCode{..} = do
initDynLinker hsc_env
let dl = hsc_dynLinker hsc_env
modifyPLS dl $ \pls0 -> do
(pls, ok) <- linkDependencies hsc_env pls0 span needed_mods
if failed ok
then throwGhcExceptionIO (ProgramError "")
else do
let ie = plusNameEnv (itbl_env pls) bc_itbls
ce = closure_env pls
new_bindings <- linkSomeBCOs hsc_env ie ce [cbc]
nms_fhvs <- makeForeignNamedHValueRefs hsc_env new_bindings
let pls2 = pls { closure_env = extendClosureEnv ce nms_fhvs
, itbl_env = ie }
return (pls2, ())
where
free_names = uniqDSetToList $
foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet bc_bcos
needed_mods :: [Module]
needed_mods = [ nameModule n | n <- free_names,
isExternalName n,
not (isWiredInName n)
]
linkModule :: HscEnv -> Module -> IO ()
linkModule hsc_env mod = do
initDynLinker hsc_env
let dl = hsc_dynLinker hsc_env
modifyPLS_ dl $ \pls -> do
(pls', ok) <- linkDependencies hsc_env pls noSrcSpan [mod]
if (failed ok) then throwGhcExceptionIO (ProgramError "could not link module")
else return pls'
linkModules :: HscEnv -> PersistentLinkerState -> [Linkable]
-> IO (PersistentLinkerState, SuccessFlag)
linkModules hsc_env pls linkables
= mask_ $ do
let (objs, bcos) = partition isObjectLinkable
(concatMap partitionLinkable linkables)
(pls1, ok_flag) <- dynLinkObjs hsc_env pls objs
if failed ok_flag then
return (pls1, Failed)
else do
pls2 <- dynLinkBCOs hsc_env pls1 bcos
return (pls2, Succeeded)
partitionLinkable :: Linkable -> [Linkable]
partitionLinkable li
= let li_uls = linkableUnlinked li
li_uls_obj = filter isObject li_uls
li_uls_bco = filter isInterpretable li_uls
in
case (li_uls_obj, li_uls_bco) of
(_:_, _:_) -> [li {linkableUnlinked=li_uls_obj},
li {linkableUnlinked=li_uls_bco}]
_ -> [li]
findModuleLinkable_maybe :: [Linkable] -> Module -> Maybe Linkable
findModuleLinkable_maybe lis mod
= case [LM time nm us | LM time nm us <- lis, nm == mod] of
[] -> Nothing
[li] -> Just li
_ -> pprPanic "findModuleLinkable" (ppr mod)
linkableInSet :: Linkable -> [Linkable] -> Bool
linkableInSet l objs_loaded =
case findModuleLinkable_maybe objs_loaded (linkableModule l) of
Nothing -> False
Just m -> linkableTime l == linkableTime m
dynLinkObjs :: HscEnv -> PersistentLinkerState -> [Linkable]
-> IO (PersistentLinkerState, SuccessFlag)
dynLinkObjs hsc_env pls objs = do
let (objs_loaded', new_objs) = rmDupLinkables (objs_loaded pls) objs
pls1 = pls { objs_loaded = objs_loaded' }
unlinkeds = concatMap linkableUnlinked new_objs
wanted_objs = map nameOfObject unlinkeds
if interpreterDynamic (hscInterp hsc_env)
then do pls2 <- dynLoadObjs hsc_env pls1 wanted_objs
return (pls2, Succeeded)
else do mapM_ (loadObj hsc_env) wanted_objs
ok <- resolveObjs hsc_env
if succeeded ok then do
return (pls1, Succeeded)
else do
pls2 <- unload_wkr hsc_env [] pls1
return (pls2, Failed)
dynLoadObjs :: HscEnv -> PersistentLinkerState -> [FilePath]
-> IO PersistentLinkerState
dynLoadObjs _ pls [] = return pls
dynLoadObjs hsc_env pls@PersistentLinkerState{..} objs = do
let dflags = hsc_dflags hsc_env
let platform = targetPlatform dflags
let minus_ls = [ lib | Option ('-':'l':lib) <- ldInputs dflags ]
let minus_big_ls = [ lib | Option ('-':'L':lib) <- ldInputs dflags ]
(soFile, libPath , libName) <-
newTempLibName dflags TFL_CurrentModule (soExt platform)
let
dflags2 = dflags {
ldInputs =
concatMap (\l -> [ Option ("-l" ++ l) ])
(nub $ snd <$> temp_sos)
++ concatMap (\lp -> Option ("-L" ++ lp)
: if gopt Opt_RPath dflags
then [ Option "-Xlinker"
, Option "-rpath"
, Option "-Xlinker"
, Option lp ]
else [])
(nub $ fst <$> temp_sos)
++ concatMap
(\lp -> Option ("-L" ++ lp)
: if gopt Opt_RPath dflags
then [ Option "-Xlinker"
, Option "-rpath"
, Option "-Xlinker"
, Option lp ]
else [])
minus_big_ls
++ map (\l -> Option ("-l" ++ l)) minus_ls,
ways = Set.singleton WayDyn,
outputFile = Just soFile
}
linkDynLib dflags2 objs pkgs_loaded
changeTempFilesLifetime dflags TFL_GhcSession [soFile]
m <- loadDLL hsc_env soFile
case m of
Nothing -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
Just err -> linkFail msg err
where
msg = "GHC.Runtime.Linker.dynLoadObjs: Loading temp shared object failed"
rmDupLinkables :: [Linkable]
-> [Linkable]
-> ([Linkable],
[Linkable])
rmDupLinkables already ls
= go already [] ls
where
go already extras [] = (already, extras)
go already extras (l:ls)
| linkableInSet l already = go already extras ls
| otherwise = go (l:already) (l:extras) ls
dynLinkBCOs :: HscEnv -> PersistentLinkerState -> [Linkable]
-> IO PersistentLinkerState
dynLinkBCOs hsc_env pls bcos = do
let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
pls1 = pls { bcos_loaded = bcos_loaded' }
unlinkeds :: [Unlinked]
unlinkeds = concatMap linkableUnlinked new_bcos
cbcs :: [CompiledByteCode]
cbcs = map byteCodeOfObject unlinkeds
ies = map bc_itbls cbcs
gce = closure_env pls
final_ie = foldr plusNameEnv (itbl_env pls) ies
names_and_refs <- linkSomeBCOs hsc_env final_ie gce cbcs
let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
freeHValueRefs hsc_env (map snd to_drop)
new_binds <- makeForeignNamedHValueRefs hsc_env to_add
return pls1 { closure_env = extendClosureEnv gce new_binds,
itbl_env = final_ie }
linkSomeBCOs :: HscEnv
-> ItblEnv
-> ClosureEnv
-> [CompiledByteCode]
-> IO [(Name,HValueRef)]
linkSomeBCOs hsc_env ie ce mods = foldr fun do_link mods []
where
fun CompiledByteCode{..} inner accum =
case bc_breaks of
Nothing -> inner ((panic "linkSomeBCOs: no break array", bc_bcos) : accum)
Just mb -> withForeignRef (modBreaks_flags mb) $ \breakarray ->
inner ((breakarray, bc_bcos) : accum)
do_link [] = return []
do_link mods = do
let flat = [ (breakarray, bco) | (breakarray, bcos) <- mods, bco <- bcos ]
names = map (unlinkedBCOName . snd) flat
bco_ix = mkNameEnv (zip names [0..])
resolved <- sequence [ linkBCO hsc_env ie ce bco_ix breakarray bco
| (breakarray, bco) <- flat ]
hvrefs <- createBCOs hsc_env resolved
return (zip names hvrefs)
makeForeignNamedHValueRefs
:: HscEnv -> [(Name,HValueRef)] -> IO [(Name,ForeignHValue)]
makeForeignNamedHValueRefs hsc_env bindings =
mapM (\(n, hvref) -> (n,) <$> mkFinalizedHValue hsc_env hvref) bindings
unload :: HscEnv
-> [Linkable]
-> IO ()
unload hsc_env linkables
= mask_ $ do
initDynLinker hsc_env
let dl = hsc_dynLinker hsc_env
new_pls
<- modifyPLS dl $ \pls -> do
pls1 <- unload_wkr hsc_env linkables pls
return (pls1, pls1)
let dflags = hsc_dflags hsc_env
debugTraceMsg dflags 3 $
text "unload: retaining objs" <+> ppr (objs_loaded new_pls)
debugTraceMsg dflags 3 $
text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls)
return ()
unload_wkr :: HscEnv
-> [Linkable]
-> PersistentLinkerState
-> IO PersistentLinkerState
unload_wkr hsc_env keep_linkables pls@PersistentLinkerState{..} = do
let (objs_to_keep, bcos_to_keep) = partition isObjectLinkable keep_linkables
discard keep l = not (linkableInSet l keep)
(objs_to_unload, remaining_objs_loaded) =
partition (discard objs_to_keep) objs_loaded
(bcos_to_unload, remaining_bcos_loaded) =
partition (discard bcos_to_keep) bcos_loaded
mapM_ unloadObjs objs_to_unload
mapM_ unloadObjs bcos_to_unload
when (not (null (objs_to_unload ++
filter (not . null . linkableObjs) bcos_to_unload))) $
purgeLookupSymbolCache hsc_env
let !bcos_retained = mkModuleSet $ map linkableModule remaining_bcos_loaded
keep_name (n,_) = isExternalName n &&
nameModule n `elemModuleSet` bcos_retained
itbl_env' = filterNameEnv keep_name itbl_env
closure_env' = filterNameEnv keep_name closure_env
!new_pls = pls { itbl_env = itbl_env',
closure_env = closure_env',
bcos_loaded = remaining_bcos_loaded,
objs_loaded = remaining_objs_loaded }
return new_pls
where
unloadObjs :: Linkable -> IO ()
unloadObjs lnk
| isWindowsHost = return ()
| hostIsDynamic = return ()
| otherwise
= mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk]
data LibrarySpec
= Objects [FilePath]
| Archive FilePath
| DLL String
| DLLPath FilePath
| Framework String
instance Outputable LibrarySpec where
ppr (Objects objs) = text "Objects" <+> ppr objs
ppr (Archive a) = text "Archive" <+> text a
ppr (DLL s) = text "DLL" <+> text s
ppr (DLLPath f) = text "DLLPath" <+> text f
ppr (Framework s) = text "Framework" <+> text s
partOfGHCi :: [PackageName]
partOfGHCi
| isWindowsHost || isDarwinHost = []
| otherwise = map (PackageName . mkFastString)
["base", "template-haskell", "editline"]
showLS :: LibrarySpec -> String
showLS (Objects nms) = "(static) [" ++ intercalate ", " nms ++ "]"
showLS (Archive nm) = "(static archive) " ++ nm
showLS (DLL nm) = "(dynamic) " ++ nm
showLS (DLLPath nm) = "(dynamic) " ++ nm
showLS (Framework nm) = "(framework) " ++ nm
linkPackages :: HscEnv -> [UnitId] -> IO ()
linkPackages hsc_env new_pkgs = do
initDynLinker hsc_env
let dl = hsc_dynLinker hsc_env
modifyPLS_ dl $ \pls -> do
linkPackages' hsc_env new_pkgs pls
linkPackages' :: HscEnv -> [UnitId] -> PersistentLinkerState
-> IO PersistentLinkerState
linkPackages' hsc_env new_pks pls = do
pkgs' <- link (pkgs_loaded pls) new_pks
return $! pls { pkgs_loaded = pkgs' }
where
dflags = hsc_dflags hsc_env
pkgstate = unitState dflags
link :: [UnitId] -> [UnitId] -> IO [UnitId]
link pkgs new_pkgs =
foldM link_one pkgs new_pkgs
link_one pkgs new_pkg
| new_pkg `elem` pkgs
= return pkgs
| Just pkg_cfg <- lookupUnitId pkgstate new_pkg
= do {
pkgs' <- link pkgs (unitDepends pkg_cfg)
; linkPackage hsc_env pkg_cfg
; return (new_pkg : pkgs') }
| otherwise
= throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
linkPackage :: HscEnv -> UnitInfo -> IO ()
linkPackage hsc_env pkg
= do
let dflags = hsc_dflags hsc_env
platform = targetPlatform dflags
is_dyn = interpreterDynamic (hscInterp hsc_env)
dirs | is_dyn = Packages.unitLibraryDynDirs pkg
| otherwise = Packages.unitLibraryDirs pkg
let hs_libs = Packages.unitLibraries pkg
hs_libs' = filter ("HSffi" /=) hs_libs
extra_libs =
(if null (Packages.unitExtDepLibsGhc pkg)
then Packages.unitExtDepLibsSys pkg
else Packages.unitExtDepLibsGhc pkg)
++ [ lib | '-':'l':lib <- Packages.unitLinkerOptions pkg ]
gcc_paths <- getGCCPaths dflags (platformOS platform)
dirs_env <- addEnvPaths "LIBRARY_PATH" dirs
hs_classifieds
<- mapM (locateLib hsc_env True dirs_env gcc_paths) hs_libs'
extra_classifieds
<- mapM (locateLib hsc_env False dirs_env gcc_paths) extra_libs
let classifieds = hs_classifieds ++ extra_classifieds
let known_dlls = [ dll | DLLPath dll <- classifieds ]
dlls = [ dll | DLL dll <- classifieds ]
objs = [ obj | Objects objs <- classifieds
, obj <- objs ]
archs = [ arch | Archive arch <- classifieds ]
let dll_paths = map takeDirectory known_dlls
all_paths = nub $ map normalise $ dll_paths ++ dirs
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath hsc_env) all_paths_env
maybePutStr dflags
("Loading package " ++ unitPackageIdString pkg ++ " ... ")
#if defined(CAN_LOAD_DLL)
when (unitPackageName pkg `notElem` partOfGHCi) $ do
loadFrameworks hsc_env platform pkg
mapM_ (load_dyn hsc_env True) known_dlls
mapM_ (load_dyn hsc_env (not is_dyn) . mkSOName platform) dlls
#endif
mapM_ (loadObj hsc_env) objs
mapM_ (loadArchive hsc_env) archs
maybePutStr dflags "linking ... "
ok <- resolveObjs hsc_env
mapM_ (removeLibrarySearchPath hsc_env) $ reverse pathCache
if succeeded ok
then maybePutStrLn dflags "done."
else let errmsg = "unable to load package `"
++ unitPackageIdString pkg ++ "'"
in throwGhcExceptionIO (InstallationError errmsg)
load_dyn :: HscEnv -> Bool -> FilePath -> IO ()
load_dyn hsc_env crash_early dll = do
r <- loadDLL hsc_env dll
case r of
Nothing -> return ()
Just err ->
if crash_early
then cmdLineErrorIO err
else let dflags = hsc_dflags hsc_env in
when (wopt Opt_WarnMissedExtraSharedLib dflags)
$ putLogMsg dflags
(Reason Opt_WarnMissedExtraSharedLib) SevWarning
noSrcSpan $ withPprStyle defaultUserStyle (note err)
where
note err = vcat $ map text
[ err
, "It's OK if you don't want to use symbols from it directly."
, "(the package DLL is loaded by the system linker"
, " which manages dependencies by itself)." ]
loadFrameworks :: HscEnv -> Platform -> UnitInfo -> IO ()
loadFrameworks hsc_env platform pkg
= when (platformUsesFrameworks platform) $ mapM_ load frameworks
where
fw_dirs = Packages.unitExtDepFrameworkDirs pkg
frameworks = Packages.unitExtDepFrameworks pkg
load fw = do r <- loadFramework hsc_env fw_dirs fw
case r of
Nothing -> return ()
Just err -> cmdLineErrorIO ("can't load framework: "
++ fw ++ " (" ++ err ++ ")" )
locateLib :: HscEnv -> Bool -> [FilePath] -> [FilePath] -> String
-> IO LibrarySpec
locateLib hsc_env is_hs lib_dirs gcc_dirs lib
| not is_hs
=
#if defined(CAN_LOAD_DLL)
findDll user `orElse`
#endif
tryImpLib user `orElse`
#if defined(CAN_LOAD_DLL)
findDll gcc `orElse`
findSysDll `orElse`
#endif
tryImpLib gcc `orElse`
findArchive `orElse`
tryGcc `orElse`
assumeDll
| loading_dynamic_hs_libs
= findHSDll `orElse`
findDynObject `orElse`
assumeDll
| otherwise
= findObject `orElse`
findArchive `orElse`
assumeDll
where
dflags = hsc_dflags hsc_env
interp = hscInterp hsc_env
dirs = lib_dirs ++ gcc_dirs
gcc = False
user = True
obj_file
| is_hs && loading_profiled_hs_libs = lib <.> "p_o"
| otherwise = lib <.> "o"
dyn_obj_file = lib <.> "dyn_o"
arch_files = [ "lib" ++ lib ++ lib_tag <.> "a"
, lib <.> "a"
, "lib" ++ lib, lib
]
lib_tag = if is_hs && loading_profiled_hs_libs then "_p" else ""
loading_profiled_hs_libs = interpreterProfiled interp
loading_dynamic_hs_libs = interpreterDynamic interp
import_libs = [ lib <.> "lib" , "lib" ++ lib <.> "lib"
, "lib" ++ lib <.> "dll.a", lib <.> "dll.a"
]
hs_dyn_lib_name = lib ++ '-':programName dflags ++ projectVersion dflags
hs_dyn_lib_file = mkHsSOName platform hs_dyn_lib_name
so_name = mkSOName platform lib
lib_so_name = "lib" ++ so_name
dyn_lib_file = case (arch, os) of
(ArchX86_64, OSSolaris2) -> "64" </> so_name
_ -> so_name
findObject = liftM (fmap $ Objects . (:[])) $ findFile dirs obj_file
findDynObject = liftM (fmap $ Objects . (:[])) $ findFile dirs dyn_obj_file
findArchive = let local name = liftM (fmap Archive) $ findFile dirs name
in apply (map local arch_files)
findHSDll = liftM (fmap DLLPath) $ findFile dirs hs_dyn_lib_file
findDll re = let dirs' = if re == user then lib_dirs else gcc_dirs
in liftM (fmap DLLPath) $ findFile dirs' dyn_lib_file
findSysDll = fmap (fmap $ DLL . dropExtension . takeFileName) $
findSystemLibrary hsc_env so_name
tryGcc = let search = searchForLibUsingGcc dflags
dllpath = liftM (fmap DLLPath)
short = dllpath $ search so_name lib_dirs
full = dllpath $ search lib_so_name lib_dirs
gcc name = liftM (fmap Archive) $ search name lib_dirs
files = import_libs ++ arch_files
dlls = [short, full]
archives = map gcc files
in apply $
#if defined(CAN_LOAD_DLL)
dlls ++
#endif
archives
tryImpLib re = case os of
OSMinGW32 ->
let dirs' = if re == user then lib_dirs else gcc_dirs
implib name = liftM (fmap Archive) $
findFile dirs' name
in apply (map implib import_libs)
_ -> return Nothing
assumeDll
| is_hs
, not loading_dynamic_hs_libs
, interpreterProfiled interp
= do
warningMsg dflags
(text "Interpreter failed to load profiled static library" <+> text lib <> char '.' $$
text " \tTrying dynamic library instead. If this fails try to rebuild" <+>
text "libraries with profiling support.")
return (DLL lib)
| otherwise = return (DLL lib)
infixr `orElse`
f `orElse` g = f >>= maybe g return
apply :: [IO (Maybe a)] -> IO (Maybe a)
apply [] = return Nothing
apply (x:xs) = do x' <- x
if isJust x'
then return x'
else apply xs
platform = targetPlatform dflags
arch = platformArch platform
os = platformOS platform
searchForLibUsingGcc :: DynFlags -> String -> [FilePath] -> IO (Maybe FilePath)
searchForLibUsingGcc dflags so dirs = do
str <- askLd dflags (map (FileOption "-B") dirs
++ [Option "--print-file-name", Option so])
let file = case lines str of
[] -> ""
l:_ -> l
if (file == so)
then return Nothing
else do b <- doesFileExist file
return (if b then Just file else Nothing)
getGCCPaths :: DynFlags -> OS -> IO [FilePath]
getGCCPaths dflags os
= case os of
OSMinGW32 ->
do gcc_dirs <- getGccSearchDirectory dflags "libraries"
sys_dirs <- getSystemDirectories
return $ nub $ gcc_dirs ++ sys_dirs
_ -> return []
gccSearchDirCache :: IORef [(String, [String])]
gccSearchDirCache = unsafePerformIO $ newIORef []
getGccSearchDirectory :: DynFlags -> String -> IO [FilePath]
getGccSearchDirectory dflags key = do
cache <- readIORef gccSearchDirCache
case lookup key cache of
Just x -> return x
Nothing -> do
str <- askLd dflags [Option "--print-search-dirs"]
let line = dropWhile isSpace str
name = key ++ ": ="
if null line
then return []
else do let val = split $ find name line
dirs <- filterM doesDirectoryExist val
modifyIORef' gccSearchDirCache ((key, dirs):)
return val
where split :: FilePath -> [FilePath]
split r = case break (==';') r of
(s, [] ) -> [s]
(s, (_:xs)) -> s : split xs
find :: String -> String -> String
find r x = let lst = lines x
val = filter (r `isPrefixOf`) lst
in if null val
then []
else case break (=='=') (head val) of
(_ , []) -> []
(_, (_:xs)) -> xs
getSystemDirectories :: IO [FilePath]
#if defined(mingw32_HOST_OS)
getSystemDirectories = fmap (:[]) getSystemDirectory
#else
getSystemDirectories = return []
#endif
addEnvPaths :: String -> [String] -> IO [String]
addEnvPaths name list
= do
working_dir <- getCurrentDirectory
values <- lookupEnv name
case values of
Nothing -> return list
Just arr -> return $ list ++ splitEnv working_dir arr
where
splitEnv :: FilePath -> String -> [String]
splitEnv working_dir value =
case break (== envListSep) value of
(x, [] ) ->
[if null x then working_dir else x]
(x, (_:xs)) ->
(if null x then working_dir else x) : splitEnv working_dir xs
#if defined(mingw32_HOST_OS)
envListSep = ';'
#else
envListSep = ':'
#endif
loadFramework :: HscEnv -> [FilePath] -> FilePath -> IO (Maybe String)
loadFramework hsc_env extraPaths rootname
= do { either_dir <- tryIO getHomeDirectory
; let homeFrameworkPath = case either_dir of
Left _ -> []
Right dir -> [dir </> "Library/Frameworks"]
ps = extraPaths ++ homeFrameworkPath ++ defaultFrameworkPaths
; errs <- findLoadDLL ps []
; return $ fmap (intercalate ", ") errs
}
where
fwk_file = rootname <.> "framework" </> rootname
defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
findLoadDLL [] errs =
return $ Just errs
findLoadDLL (p:ps) errs =
do { dll <- loadDLL hsc_env (p </> fwk_file)
; case dll of
Nothing -> return Nothing
Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
}
maybePutStr :: DynFlags -> String -> IO ()
maybePutStr dflags s
= when (verbosity dflags > 1) $
putLogMsg dflags
NoReason
SevInteractive
noSrcSpan
$ withPprStyle defaultUserStyle (text s)
maybePutStrLn :: DynFlags -> String -> IO ()
maybePutStrLn dflags s = maybePutStr dflags (s ++ "\n")