{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
module GHC.Linker.Loader
( Loader (..)
, LoaderState (..)
, initLoaderState
, uninitializedLoader
, showLoaderState
, getLoaderState
, loadExpr
, loadDecls
, loadPackages
, loadModule
, loadCmdLineLibs
, loadName
, unload
, withExtendedLoadedEnv
, extendLoadedEnv
, deleteFromLoadedEnv
, rmDupLinkables
, modifyLoaderState
, initLinkDepsOpts
, getGccSearchDirectory
)
where
import GHC.Prelude
import GHC.Settings
import GHC.Platform
import GHC.Platform.Ways
import GHC.Driver.Phases
import GHC.Driver.Env
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Driver.Config.Diagnostic
import GHC.Driver.Config.Finder
import GHC.Tc.Utils.Monad
import GHC.Runtime.Interpreter
import GHCi.RemoteTypes
import GHC.Iface.Load
import GHCi.Message (LoadedDLL)
import GHC.ByteCode.Linker
import GHC.ByteCode.Asm
import GHC.ByteCode.Types
import GHC.SysTools
import GHC.Types.Basic
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.SrcLoc
import GHC.Types.Unique.DSet
import GHC.Types.Unique.DFM
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Error
import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Unit.Env
import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode))
import GHC.Unit.Module
import GHC.Unit.State as Packages
import qualified GHC.Data.ShortText as ST
import GHC.Data.FastString
import GHC.Linker.Deps
import GHC.Linker.MacOS
import GHC.Linker.Dynamic
import GHC.Linker.Types
import Control.Monad
import qualified Data.Set as Set
import Data.Char (isSpace)
import qualified Data.Foldable as Foldable
import Data.IORef
import Data.List (intercalate, isPrefixOf, nub, partition)
import Data.Maybe
import Control.Concurrent.MVar
import qualified Control.Monad.Catch as MC
import qualified Data.List.NonEmpty as NE
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
uninitialised :: a
uninitialised :: forall a. a
uninitialised = String -> a
forall a. HasCallStack => String -> a
panic String
"Loader not initialised"
modifyLoaderState_ :: Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ :: Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ Interp
interp LoaderState -> IO LoaderState
f =
MVar (Maybe LoaderState)
-> (Maybe LoaderState -> IO (Maybe LoaderState)) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ (Loader -> MVar (Maybe LoaderState)
loader_state (Interp -> Loader
interpLoader Interp
interp))
((LoaderState -> Maybe LoaderState)
-> IO LoaderState -> IO (Maybe LoaderState)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LoaderState -> Maybe LoaderState
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO LoaderState -> IO (Maybe LoaderState))
-> (Maybe LoaderState -> IO LoaderState)
-> Maybe LoaderState
-> IO (Maybe LoaderState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoaderState -> IO LoaderState
f (LoaderState -> IO LoaderState)
-> (Maybe LoaderState -> LoaderState)
-> Maybe LoaderState
-> IO LoaderState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoaderState -> Maybe LoaderState -> LoaderState
forall a. a -> Maybe a -> a
fromMaybe LoaderState
forall a. a
uninitialised)
modifyLoaderState :: Interp -> (LoaderState -> IO (LoaderState, a)) -> IO a
modifyLoaderState :: forall a. Interp -> (LoaderState -> IO (LoaderState, a)) -> IO a
modifyLoaderState Interp
interp LoaderState -> IO (LoaderState, a)
f =
MVar (Maybe LoaderState)
-> (Maybe LoaderState -> IO (Maybe LoaderState, a)) -> IO a
forall a b. MVar a -> (a -> IO (a, b)) -> IO b
modifyMVar (Loader -> MVar (Maybe LoaderState)
loader_state (Interp -> Loader
interpLoader Interp
interp))
((LoaderState -> Maybe LoaderState)
-> IO (LoaderState, a) -> IO (Maybe LoaderState, a)
forall {f :: * -> *} {t} {a} {b}.
Functor f =>
(t -> a) -> f (t, b) -> f (a, b)
fmapFst LoaderState -> Maybe LoaderState
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO (LoaderState, a) -> IO (Maybe LoaderState, a))
-> (Maybe LoaderState -> IO (LoaderState, a))
-> Maybe LoaderState
-> IO (Maybe LoaderState, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoaderState -> IO (LoaderState, a)
f (LoaderState -> IO (LoaderState, a))
-> (Maybe LoaderState -> LoaderState)
-> Maybe LoaderState
-> IO (LoaderState, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoaderState -> Maybe LoaderState -> LoaderState
forall a. a -> Maybe a -> a
fromMaybe LoaderState
forall a. a
uninitialised)
where fmapFst :: (t -> a) -> f (t, b) -> f (a, b)
fmapFst t -> a
f = ((t, b) -> (a, b)) -> f (t, b) -> f (a, b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(t
x, b
y) -> (t -> a
f t
x, b
y))
getLoaderState :: Interp -> IO (Maybe LoaderState)
getLoaderState :: Interp -> IO (Maybe LoaderState)
getLoaderState Interp
interp = MVar (Maybe LoaderState) -> IO (Maybe LoaderState)
forall a. MVar a -> IO a
readMVar (Loader -> MVar (Maybe LoaderState)
loader_state (Interp -> Loader
interpLoader Interp
interp))
emptyLoaderState :: LoaderState
emptyLoaderState :: LoaderState
emptyLoaderState = LoaderState
{ linker_env :: LinkerEnv
linker_env = LinkerEnv
{ closure_env :: ClosureEnv
closure_env = ClosureEnv
forall a. NameEnv a
emptyNameEnv
, itbl_env :: ItblEnv
itbl_env = ItblEnv
forall a. NameEnv a
emptyNameEnv
, addr_env :: AddrEnv
addr_env = AddrEnv
forall a. NameEnv a
emptyNameEnv
}
, pkgs_loaded :: PkgsLoaded
pkgs_loaded = PkgsLoaded
init_pkgs
, bcos_loaded :: LinkableSet
bcos_loaded = LinkableSet
forall a. ModuleEnv a
emptyModuleEnv
, objs_loaded :: LinkableSet
objs_loaded = LinkableSet
forall a. ModuleEnv a
emptyModuleEnv
, temp_sos :: [(String, String)]
temp_sos = []
}
where init_pkgs :: PkgsLoaded
init_pkgs = UnitId -> LoadedPkgInfo -> PkgsLoaded
forall key elt. Uniquable key => key -> elt -> UniqDFM key elt
unitUDFM UnitId
rtsUnitId (UnitId
-> [LibrarySpec]
-> [LibrarySpec]
-> [RemotePtr LoadedDLL]
-> UniqDSet UnitId
-> LoadedPkgInfo
LoadedPkgInfo UnitId
rtsUnitId [] [] [] UniqDSet UnitId
forall a. UniqDSet a
emptyUniqDSet)
extendLoadedEnv :: Interp -> [(Name,ForeignHValue)] -> IO ()
extendLoadedEnv :: Interp -> [(Name, ForeignHValue)] -> IO ()
extendLoadedEnv Interp
interp [(Name, ForeignHValue)]
new_bindings =
Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ Interp
interp ((LoaderState -> IO LoaderState) -> IO ())
-> (LoaderState -> IO LoaderState) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls -> do
LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState -> IO LoaderState) -> LoaderState -> IO LoaderState
forall a b. (a -> b) -> a -> b
$! LoaderState -> (ClosureEnv -> ClosureEnv) -> LoaderState
modifyClosureEnv LoaderState
pls ((ClosureEnv -> ClosureEnv) -> LoaderState)
-> (ClosureEnv -> ClosureEnv) -> LoaderState
forall a b. (a -> b) -> a -> b
$ \ClosureEnv
ce ->
ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv
extendClosureEnv ClosureEnv
ce [(Name, ForeignHValue)]
new_bindings
deleteFromLoadedEnv :: Interp -> [Name] -> IO ()
deleteFromLoadedEnv :: Interp -> [Name] -> IO ()
deleteFromLoadedEnv Interp
interp [Name]
to_remove =
Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ Interp
interp ((LoaderState -> IO LoaderState) -> IO ())
-> (LoaderState -> IO LoaderState) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls -> do
LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState -> IO LoaderState) -> LoaderState -> IO LoaderState
forall a b. (a -> b) -> a -> b
$ LoaderState -> (ClosureEnv -> ClosureEnv) -> LoaderState
modifyClosureEnv LoaderState
pls ((ClosureEnv -> ClosureEnv) -> LoaderState)
-> (ClosureEnv -> ClosureEnv) -> LoaderState
forall a b. (a -> b) -> a -> b
$ \ClosureEnv
ce ->
ClosureEnv -> [Name] -> ClosureEnv
forall a. NameEnv a -> [Name] -> NameEnv a
delListFromNameEnv ClosureEnv
ce [Name]
to_remove
loadName :: Interp -> HscEnv -> Name -> IO (ForeignHValue, [Linkable], PkgsLoaded)
loadName :: Interp
-> HscEnv -> Name -> IO (ForeignHValue, [Linkable], PkgsLoaded)
loadName Interp
interp HscEnv
hsc_env Name
name = do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
Interp
-> (LoaderState
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded)))
-> IO (ForeignHValue, [Linkable], PkgsLoaded)
forall a. Interp -> (LoaderState -> IO (LoaderState, a)) -> IO a
modifyLoaderState Interp
interp ((LoaderState
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded)))
-> IO (ForeignHValue, [Linkable], PkgsLoaded))
-> (LoaderState
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded)))
-> IO (ForeignHValue, [Linkable], PkgsLoaded)
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls0 -> do
(pls, links, pkgs) <- if Bool -> Bool
not (Name -> Bool
isExternalName Name
name)
then (LoaderState, [Linkable], PkgsLoaded)
-> IO (LoaderState, [Linkable], PkgsLoaded)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls0, [], PkgsLoaded
forall {k} (key :: k) elt. UniqDFM key elt
emptyUDFM)
else do
(pls', ok, links, pkgs) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls0 SrcSpan
noSrcSpan
[HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name]
if failed ok
then throwGhcExceptionIO (ProgramError "")
else return (pls', links, pkgs)
case lookupNameEnv (closure_env (linker_env pls)) name of
Just (Name
_,ForeignHValue
aa) -> (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls,(ForeignHValue
aa, [Linkable]
links, PkgsLoaded
pkgs))
Maybe (Name, ForeignHValue)
Nothing -> Bool
-> SDoc
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Name -> Bool
isExternalName Name
name) (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name) (IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded)))
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
-> IO (LoaderState, (ForeignHValue, [Linkable], PkgsLoaded))
forall a b. (a -> b) -> a -> b
$
do let sym_to_find :: FastString
sym_to_find = Name -> String -> FastString
nameToCLabel Name
name String
"closure"
m <- Interp -> String -> IO (Maybe HValueRef)
lookupClosure Interp
interp (FastString -> String
unpackFS FastString
sym_to_find)
r <- case m of
Just HValueRef
hvref -> Interp -> HValueRef -> IO ForeignHValue
forall a. Interp -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue Interp
interp HValueRef
hvref
Maybe HValueRef
Nothing -> String -> String -> IO ForeignHValue
forall a. String -> String -> IO a
linkFail String
"GHC.Linker.Loader.loadName"
(FastString -> String
unpackFS FastString
sym_to_find)
return (pls,(r, links, pkgs))
loadDependencies
:: Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies :: Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls SrcSpan
span [Module]
needed_mods = do
let opts :: LinkDepsOpts
opts = HscEnv -> LinkDepsOpts
initLinkDepsOpts HscEnv
hsc_env
deps <- LinkDepsOpts
-> Interp -> LoaderState -> SrcSpan -> [Module] -> IO LinkDeps
getLinkDeps LinkDepsOpts
opts Interp
interp LoaderState
pls SrcSpan
span [Module]
needed_mods
let this_pkgs_needed = LinkDeps -> UniqDSet UnitId
ldNeededUnits LinkDeps
deps
pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
(pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
let this_pkgs_loaded = PkgsLoaded -> UniqDFM UnitId UnitId -> PkgsLoaded
forall {k} (key :: k) elt elt2.
UniqDFM key elt -> UniqDFM key elt2 -> UniqDFM key elt
udfmRestrictKeys PkgsLoaded
all_pkgs_loaded (UniqDFM UnitId UnitId -> PkgsLoaded)
-> UniqDFM UnitId UnitId -> PkgsLoaded
forall a b. (a -> b) -> a -> b
$ UniqDSet UnitId -> UniqDFM UnitId UnitId
forall a. UniqDSet a -> UniqDFM a a
getUniqDSet UniqDSet UnitId
trans_pkgs_needed
all_pkgs_loaded = LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls2
trans_pkgs_needed = [UniqDSet UnitId] -> UniqDSet UnitId
forall a. [UniqDSet a] -> UniqDSet a
unionManyUniqDSets (UniqDSet UnitId
this_pkgs_needed UniqDSet UnitId -> [UniqDSet UnitId] -> [UniqDSet UnitId]
forall a. a -> [a] -> [a]
: [ LoadedPkgInfo -> UniqDSet UnitId
loaded_pkg_trans_deps LoadedPkgInfo
pkg
| UnitId
pkg_id <- UniqDSet UnitId -> [UnitId]
forall a. UniqDSet a -> [a]
uniqDSetToList UniqDSet UnitId
this_pkgs_needed
, Just LoadedPkgInfo
pkg <- [PkgsLoaded -> UnitId -> Maybe LoadedPkgInfo
forall key elt.
Uniquable key =>
UniqDFM key elt -> key -> Maybe elt
lookupUDFM PkgsLoaded
all_pkgs_loaded UnitId
pkg_id]
])
return (pls2, succ, ldAllLinkables deps, this_pkgs_loaded)
withExtendedLoadedEnv
:: (ExceptionMonad m)
=> Interp
-> [(Name,ForeignHValue)]
-> m a
-> m a
withExtendedLoadedEnv :: forall (m :: * -> *) a.
ExceptionMonad m =>
Interp -> [(Name, ForeignHValue)] -> m a -> m a
withExtendedLoadedEnv Interp
interp [(Name, ForeignHValue)]
new_env m a
action
= m () -> (() -> m ()) -> (() -> m a) -> m a
forall (m :: * -> *) a c b.
(HasCallStack, MonadMask m) =>
m a -> (a -> m c) -> (a -> m b) -> m b
MC.bracket (IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Interp -> [(Name, ForeignHValue)] -> IO ()
extendLoadedEnv Interp
interp [(Name, ForeignHValue)]
new_env)
(\()
_ -> m ()
reset_old_env)
(\()
_ -> m a
action)
where
reset_old_env :: m ()
reset_old_env = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
Interp -> [Name] -> IO ()
deleteFromLoadedEnv Interp
interp (((Name, ForeignHValue) -> Name)
-> [(Name, ForeignHValue)] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (Name, ForeignHValue) -> Name
forall a b. (a, b) -> a
fst [(Name, ForeignHValue)]
new_env)
showLoaderState :: Interp -> IO SDoc
showLoaderState :: Interp -> IO SDoc
showLoaderState Interp
interp = do
ls <- MVar (Maybe LoaderState) -> IO (Maybe LoaderState)
forall a. MVar a -> IO a
readMVar (Loader -> MVar (Maybe LoaderState)
loader_state (Interp -> Loader
interpLoader Interp
interp))
let docs = case Maybe LoaderState
ls of
Maybe LoaderState
Nothing -> [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Loader not initialised"]
Just LoaderState
pls -> [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Pkgs:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [UnitId] -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((LoadedPkgInfo -> UnitId) -> [LoadedPkgInfo] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map LoadedPkgInfo -> UnitId
loaded_pkg_uid ([LoadedPkgInfo] -> [UnitId]) -> [LoadedPkgInfo] -> [UnitId]
forall a b. (a -> b) -> a -> b
$ PkgsLoaded -> [LoadedPkgInfo]
forall {k} (key :: k) elt. UniqDFM key elt -> [elt]
eltsUDFM (PkgsLoaded -> [LoadedPkgInfo]) -> PkgsLoaded -> [LoadedPkgInfo]
forall a b. (a -> b) -> a -> b
$ LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Objs:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [Linkable] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LinkableSet -> [Linkable]
forall a. ModuleEnv a -> [a]
moduleEnvElts (LinkableSet -> [Linkable]) -> LinkableSet -> [Linkable]
forall a b. (a -> b) -> a -> b
$ LoaderState -> LinkableSet
objs_loaded LoaderState
pls)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"BCOs:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [Linkable] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LinkableSet -> [Linkable]
forall a. ModuleEnv a -> [a]
moduleEnvElts (LinkableSet -> [Linkable]) -> LinkableSet -> [Linkable]
forall a b. (a -> b) -> a -> b
$ LoaderState -> LinkableSet
bcos_loaded LoaderState
pls)
]
return $ withPprStyle defaultDumpStyle
$ vcat (text "----- Loader state -----":docs)
initLoaderState :: Interp -> HscEnv -> IO ()
initLoaderState :: Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env = do
MVar (Maybe LoaderState)
-> (Maybe LoaderState -> IO (Maybe LoaderState)) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ (Loader -> MVar (Maybe LoaderState)
loader_state (Interp -> Loader
interpLoader Interp
interp)) ((Maybe LoaderState -> IO (Maybe LoaderState)) -> IO ())
-> (Maybe LoaderState -> IO (Maybe LoaderState)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Maybe LoaderState
pls -> do
case Maybe LoaderState
pls of
Just LoaderState
_ -> Maybe LoaderState -> IO (Maybe LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LoaderState
pls
Maybe LoaderState
Nothing -> LoaderState -> Maybe LoaderState
forall a. a -> Maybe a
Just (LoaderState -> Maybe LoaderState)
-> IO LoaderState -> IO (Maybe LoaderState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Interp -> HscEnv -> IO LoaderState
reallyInitLoaderState Interp
interp HscEnv
hsc_env
reallyInitLoaderState :: Interp -> HscEnv -> IO LoaderState
reallyInitLoaderState :: Interp -> HscEnv -> IO LoaderState
reallyInitLoaderState Interp
interp HscEnv
hsc_env = do
let pls0 :: LoaderState
pls0 = LoaderState
emptyLoaderState
case Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)) of
Arch
ArchJavaScript -> LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls0
Arch
_ -> do
Interp -> IO ()
initObjLinker Interp
interp
pls <- (IO LoaderState -> UnitId -> HomeUnitEnv -> IO LoaderState)
-> IO LoaderState -> UnitEnvGraph HomeUnitEnv -> IO LoaderState
forall b a. (b -> UnitId -> a -> b) -> b -> UnitEnvGraph a -> b
unitEnv_foldWithKey (\IO LoaderState
k UnitId
u HomeUnitEnv
env -> IO LoaderState
k IO LoaderState -> (LoaderState -> IO LoaderState) -> IO LoaderState
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \LoaderState
pls' -> Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' Interp
interp (HasDebugCallStack => UnitId -> HscEnv -> HscEnv
UnitId -> HscEnv -> HscEnv
hscSetActiveUnitId UnitId
u HscEnv
hsc_env) (UnitState -> [UnitId]
preloadUnits (HomeUnitEnv -> UnitState
homeUnitEnv_units HomeUnitEnv
env)) LoaderState
pls') (LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls0) (HscEnv -> UnitEnvGraph HomeUnitEnv
hsc_HUG HscEnv
hsc_env)
loadCmdLineLibs' interp hsc_env pls
loadCmdLineLibs :: Interp -> HscEnv -> IO ()
loadCmdLineLibs :: Interp -> HscEnv -> IO ()
loadCmdLineLibs Interp
interp HscEnv
hsc_env = do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ Interp
interp ((LoaderState -> IO LoaderState) -> IO ())
-> (LoaderState -> IO LoaderState) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls ->
Interp -> HscEnv -> LoaderState -> IO LoaderState
loadCmdLineLibs' Interp
interp HscEnv
hsc_env LoaderState
pls
loadCmdLineLibs' :: Interp -> HscEnv -> LoaderState -> IO LoaderState
loadCmdLineLibs' :: Interp -> HscEnv -> LoaderState -> IO LoaderState
loadCmdLineLibs' Interp
interp HscEnv
hsc_env LoaderState
pls = (Set UnitId, LoaderState) -> LoaderState
forall a b. (a, b) -> b
snd ((Set UnitId, LoaderState) -> LoaderState)
-> IO (Set UnitId, LoaderState) -> IO LoaderState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
((Set UnitId, LoaderState)
-> UnitId -> IO (Set UnitId, LoaderState))
-> (Set UnitId, LoaderState)
-> Set UnitId
-> IO (Set UnitId, LoaderState)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM
(\(Set UnitId
done', LoaderState
pls') UnitId
cur_uid -> Set UnitId -> UnitId -> LoaderState -> IO (Set UnitId, LoaderState)
load Set UnitId
done' UnitId
cur_uid LoaderState
pls')
(Set UnitId
forall a. Set a
Set.empty, LoaderState
pls)
(HscEnv -> Set UnitId
hsc_all_home_unit_ids HscEnv
hsc_env)
where
load :: Set.Set UnitId -> UnitId -> LoaderState -> IO (Set.Set UnitId, LoaderState)
load :: Set UnitId -> UnitId -> LoaderState -> IO (Set UnitId, LoaderState)
load Set UnitId
done UnitId
uid LoaderState
pls | UnitId
uid UnitId -> Set UnitId -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set UnitId
done = (Set UnitId, LoaderState) -> IO (Set UnitId, LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Set UnitId
done, LoaderState
pls)
load Set UnitId
done UnitId
uid LoaderState
pls = do
let hsc' :: HscEnv
hsc' = HasDebugCallStack => UnitId -> HscEnv -> HscEnv
UnitId -> HscEnv -> HscEnv
hscSetActiveUnitId UnitId
uid HscEnv
hsc_env
(done', pls') <- ((Set UnitId, LoaderState)
-> UnitId -> IO (Set UnitId, LoaderState))
-> (Set UnitId, LoaderState)
-> [UnitId]
-> IO (Set UnitId, LoaderState)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\(Set UnitId
done', LoaderState
pls') UnitId
uid -> Set UnitId -> UnitId -> LoaderState -> IO (Set UnitId, LoaderState)
load Set UnitId
done' UnitId
uid LoaderState
pls') (Set UnitId
done, LoaderState
pls)
(UnitState -> [UnitId]
homeUnitDepends (HasDebugCallStack => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units HscEnv
hsc'))
pls'' <- loadCmdLineLibs'' interp hsc' pls'
return $ (Set.insert uid done', pls'')
loadCmdLineLibs''
:: Interp
-> HscEnv
-> LoaderState
-> IO LoaderState
loadCmdLineLibs'' :: Interp -> HscEnv -> LoaderState -> IO LoaderState
loadCmdLineLibs'' Interp
interp HscEnv
hsc_env LoaderState
pls =
do
let dflags :: DynFlags
dflags@(DynFlags { ldInputs :: DynFlags -> [Option]
ldInputs = [Option]
cmdline_ld_inputs
, libraryPaths :: DynFlags -> [String]
libraryPaths = [String]
lib_paths_base})
= HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
let minus_ls_1 :: [String]
minus_ls_1 = [ String
lib | Option (Char
'-':Char
'l':String
lib) <- [Option]
cmdline_ld_inputs ]
let platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
os :: OS
os = Platform -> OS
platformOS Platform
platform
minus_ls :: [String]
minus_ls = case OS
os of
OS
OSMinGW32 -> String
"pthread" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
minus_ls_1
OS
_ -> [String]
minus_ls_1
gcc_paths <- Logger -> DynFlags -> OS -> IO [String]
getGCCPaths Logger
logger DynFlags
dflags OS
os
lib_paths_env <- addEnvPaths "LIBRARY_PATH" lib_paths_base
maybePutStrLn logger "Search directories (user):"
maybePutStr logger (unlines $ map (" "++) lib_paths_env)
maybePutStrLn logger "Search directories (gcc):"
maybePutStr logger (unlines $ map (" "++) gcc_paths)
libspecs
<- mapM (locateLib interp hsc_env False lib_paths_env gcc_paths) minus_ls
classified_ld_inputs <- mapM (classifyLdInput logger platform)
[ f | FileOption _ f <- cmdline_ld_inputs ]
let platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
let (framework_paths, frameworks) =
if platformUsesFrameworks platform
then (frameworkPaths dflags, cmdlineFrameworks dflags)
else ([],[])
let cmdline_lib_specs = [Maybe LibrarySpec] -> [LibrarySpec]
forall a. [Maybe a] -> [a]
catMaybes [Maybe LibrarySpec]
classified_ld_inputs
[LibrarySpec] -> [LibrarySpec] -> [LibrarySpec]
forall a. [a] -> [a] -> [a]
++ [LibrarySpec]
libspecs
[LibrarySpec] -> [LibrarySpec] -> [LibrarySpec]
forall a. [a] -> [a] -> [a]
++ (String -> LibrarySpec) -> [String] -> [LibrarySpec]
forall a b. (a -> b) -> [a] -> [b]
map String -> LibrarySpec
Framework [String]
frameworks
if null cmdline_lib_specs
then return pls
else do
let all_paths = let paths :: [String]
paths = String -> String
takeDirectory (DynFlags -> String
pgm_c DynFlags
dflags)
String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
framework_paths
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
lib_paths_base
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String -> String
takeDirectory String
dll | DLLPath String
dll <- [LibrarySpec]
libspecs ]
in [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
normalise [String]
paths
let lib_paths = [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
lib_paths_base [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
gcc_paths
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
let merged_specs = [LibrarySpec] -> [LibrarySpec]
mergeStaticObjects [LibrarySpec]
cmdline_lib_specs
pls1 <- foldM (preloadLib interp hsc_env lib_paths framework_paths) pls
merged_specs
maybePutStr logger "final link ... "
ok <- resolveObjs interp
mapM_ (removeLibrarySearchPath interp) $ reverse pathCache
if succeeded ok then maybePutStrLn logger "done"
else throwGhcExceptionIO (ProgramError "linking extra libraries/objects failed")
return pls1
mergeStaticObjects :: [LibrarySpec] -> [LibrarySpec]
mergeStaticObjects :: [LibrarySpec] -> [LibrarySpec]
mergeStaticObjects [LibrarySpec]
specs = [String] -> [LibrarySpec] -> [LibrarySpec]
go [] [LibrarySpec]
specs
where
go :: [FilePath] -> [LibrarySpec] -> [LibrarySpec]
go :: [String] -> [LibrarySpec] -> [LibrarySpec]
go [String]
accum (Objects [String]
objs : [LibrarySpec]
rest) = [String] -> [LibrarySpec] -> [LibrarySpec]
go ([String]
objs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
accum) [LibrarySpec]
rest
go accum :: [String]
accum@(String
_:[String]
_) [LibrarySpec]
rest = [String] -> LibrarySpec
Objects ([String] -> [String]
forall a. [a] -> [a]
reverse [String]
accum) LibrarySpec -> [LibrarySpec] -> [LibrarySpec]
forall a. a -> [a] -> [a]
: [String] -> [LibrarySpec] -> [LibrarySpec]
go [] [LibrarySpec]
rest
go [] (LibrarySpec
spec:[LibrarySpec]
rest) = LibrarySpec
spec LibrarySpec -> [LibrarySpec] -> [LibrarySpec]
forall a. a -> [a] -> [a]
: [String] -> [LibrarySpec] -> [LibrarySpec]
go [] [LibrarySpec]
rest
go [] [] = []
classifyLdInput :: Logger -> Platform -> FilePath -> IO (Maybe LibrarySpec)
classifyLdInput :: Logger -> Platform -> String -> IO (Maybe LibrarySpec)
classifyLdInput Logger
logger Platform
platform String
f
| Platform -> String -> Bool
isObjectFilename Platform
platform String
f = Maybe LibrarySpec -> IO (Maybe LibrarySpec)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LibrarySpec -> Maybe LibrarySpec
forall a. a -> Maybe a
Just ([String] -> LibrarySpec
Objects [String
f]))
| Platform -> String -> Bool
isDynLibFilename Platform
platform String
f = Maybe LibrarySpec -> IO (Maybe LibrarySpec)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LibrarySpec -> Maybe LibrarySpec
forall a. a -> Maybe a
Just (String -> LibrarySpec
DLLPath String
f))
| Bool
otherwise = do
Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg Logger
logger MessageClass
MCInfo SrcSpan
noSrcSpan
(SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle
(String -> SDoc
forall doc. IsLine doc => String -> doc
text (String
"Warning: ignoring unrecognised input `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"))
Maybe LibrarySpec -> IO (Maybe LibrarySpec)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LibrarySpec
forall a. Maybe a
Nothing
preloadLib
:: Interp
-> HscEnv
-> [String]
-> [String]
-> LoaderState
-> LibrarySpec
-> IO LoaderState
preloadLib :: Interp
-> HscEnv
-> [String]
-> [String]
-> LoaderState
-> LibrarySpec
-> IO LoaderState
preloadLib Interp
interp HscEnv
hsc_env [String]
lib_paths [String]
framework_paths LoaderState
pls LibrarySpec
lib_spec = do
Logger -> String -> IO ()
maybePutStr Logger
logger (String
"Loading object " String -> String -> String
forall a. [a] -> [a] -> [a]
++ LibrarySpec -> String
showLS LibrarySpec
lib_spec String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" ... ")
case LibrarySpec
lib_spec of
Objects [String]
static_ishs -> do
(b, pls1) <- [String] -> [String] -> IO (Bool, LoaderState)
preload_statics [String]
lib_paths [String]
static_ishs
maybePutStrLn logger (if b then "done" else "not found")
return pls1
Archive String
static_ish -> do
b <- [String] -> String -> IO Bool
preload_static_archive [String]
lib_paths String
static_ish
maybePutStrLn logger (if b then "done" else "not found")
return pls
DLL String
dll_unadorned -> do
maybe_errstr <- Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
loadDLL Interp
interp (Platform -> String -> String
platformSOName Platform
platform String
dll_unadorned)
case maybe_errstr of
Right RemotePtr LoadedDLL
_ -> Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
Left String
mm | Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
/= OS
OSDarwin ->
String -> [String] -> LibrarySpec -> IO ()
preloadFailed String
mm [String]
lib_paths LibrarySpec
lib_spec
Left String
mm | Bool
otherwise -> do
let libfile :: String
libfile = (String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dll_unadorned) String -> String -> String
<.> String
"so"
err2 <- Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
loadDLL Interp
interp String
libfile
case err2 of
Right RemotePtr LoadedDLL
_ -> Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
Left String
_ -> String -> [String] -> LibrarySpec -> IO ()
preloadFailed String
mm [String]
lib_paths LibrarySpec
lib_spec
return pls
DLLPath String
dll_path -> do
do maybe_errstr <- Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
loadDLL Interp
interp String
dll_path
case maybe_errstr of
Right RemotePtr LoadedDLL
_ -> Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
Left String
mm -> String -> [String] -> LibrarySpec -> IO ()
preloadFailed String
mm [String]
lib_paths LibrarySpec
lib_spec
return pls
Framework String
framework ->
if Platform -> Bool
platformUsesFrameworks (DynFlags -> Platform
targetPlatform DynFlags
dflags)
then do maybe_errstr <- Interp -> [String] -> String -> IO (Maybe String)
loadFramework Interp
interp [String]
framework_paths String
framework
case maybe_errstr of
Maybe String
Nothing -> Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
Just String
mm -> String -> [String] -> LibrarySpec -> IO ()
preloadFailed String
mm [String]
framework_paths LibrarySpec
lib_spec
return pls
else GhcException -> IO LoaderState
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"preloadLib Framework")
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
preloadFailed String
sys_errmsg [String]
paths LibrarySpec
spec
= do Logger -> String -> IO ()
maybePutStr Logger
logger String
"failed.\n"
GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO ()) -> GhcException -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> GhcException
CmdLineError (
String
"user specified .o/.so/.DLL could not be loaded ("
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
sys_errmsg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")\nWhilst trying to load: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ LibrarySpec -> String
showLS LibrarySpec
spec String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nAdditional directories searched:"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ (if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
paths then String
" (none)" else
String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
" "String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
paths)))
preload_statics :: [String] -> [String] -> IO (Bool, LoaderState)
preload_statics [String]
_paths [String]
names
= do b <- [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool) -> IO [Bool] -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO Bool) -> [String] -> IO [Bool]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO Bool
doesFileExist [String]
names
if not b then return (False, pls)
else if interpreterDynamic interp
then do pls1 <- dynLoadObjs interp hsc_env pls names
return (True, pls1)
else do mapM_ (loadObj interp) names
return (True, pls)
preload_static_archive :: [String] -> String -> IO Bool
preload_static_archive [String]
_paths String
name
= do b <- String -> IO Bool
doesFileExist String
name
if not b then return False
else do if interpreterDynamic interp
then throwGhcExceptionIO $
CmdLineError dynamic_msg
else loadArchive interp name
return True
where
dynamic_msg :: String
dynamic_msg = [String] -> String
unlines
[ String
"User-specified static library could not be loaded ("
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
, String
"Loading static libraries is not supported in this configuration."
, String
"Try using a dynamic library instead."
]
loadExpr :: Interp -> HscEnv -> SrcSpan -> UnlinkedBCO -> IO ForeignHValue
loadExpr :: Interp -> HscEnv -> SrcSpan -> UnlinkedBCO -> IO ForeignHValue
loadExpr Interp
interp HscEnv
hsc_env SrcSpan
span UnlinkedBCO
root_ul_bco = do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
Interp
-> (LoaderState -> IO (LoaderState, ForeignHValue))
-> IO ForeignHValue
forall a. Interp -> (LoaderState -> IO (LoaderState, a)) -> IO a
modifyLoaderState Interp
interp ((LoaderState -> IO (LoaderState, ForeignHValue))
-> IO ForeignHValue)
-> (LoaderState -> IO (LoaderState, ForeignHValue))
-> IO ForeignHValue
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls0 -> do
(pls, ok, _, _) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls0 SrcSpan
span [Module]
needed_mods
if failed ok
then throwGhcExceptionIO (ProgramError "")
else do
let le = LoaderState -> LinkerEnv
linker_env LoaderState
pls
bco_ix = [(Name, Int)] -> NameEnv Int
forall a. [(Name, a)] -> NameEnv a
mkNameEnv [(UnlinkedBCO -> Name
unlinkedBCOName UnlinkedBCO
root_ul_bco, Int
0)]
resolved <- linkBCO interp (pkgs_loaded pls) le bco_ix root_ul_bco
[root_hvref] <- createBCOs interp [resolved]
fhv <- mkFinalizedHValue interp root_hvref
return (pls, fhv)
where
free_names :: [Name]
free_names = UniqDSet Name -> [Name]
forall a. UniqDSet a -> [a]
uniqDSetToList (UnlinkedBCO -> UniqDSet Name
bcoFreeNames UnlinkedBCO
root_ul_bco)
needed_mods :: [Module]
needed_mods :: [Module]
needed_mods = [ HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
n | Name
n <- [Name]
free_names,
Name -> Bool
isExternalName Name
n,
Bool -> Bool
not (Name -> Bool
isWiredInName Name
n)
]
initLinkDepsOpts :: HscEnv -> LinkDepsOpts
initLinkDepsOpts :: HscEnv -> LinkDepsOpts
initLinkDepsOpts HscEnv
hsc_env = LinkDepsOpts
opts
where
opts :: LinkDepsOpts
opts = LinkDepsOpts
{ ldObjSuffix :: String
ldObjSuffix = DynFlags -> String
objectSuf DynFlags
dflags
, ldForceDyn :: Bool
ldForceDyn = Settings -> Bool
sTargetRTSLinkerOnlySupportsSharedLibs (Settings -> Bool) -> Settings -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> Settings
settings DynFlags
dflags
, ldOneShotMode :: Bool
ldOneShotMode = GhcMode -> Bool
isOneShot (DynFlags -> GhcMode
ghcMode DynFlags
dflags)
, ldModuleGraph :: ModuleGraph
ldModuleGraph = HscEnv -> ModuleGraph
hsc_mod_graph HscEnv
hsc_env
, ldUnitEnv :: UnitEnv
ldUnitEnv = HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env
, ldPprOpts :: SDocContext
ldPprOpts = DynFlags -> PprStyle -> SDocContext
initSDocContext DynFlags
dflags PprStyle
defaultUserStyle
, ldFinderCache :: FinderCache
ldFinderCache = HscEnv -> FinderCache
hsc_FC HscEnv
hsc_env
, ldFinderOpts :: FinderOpts
ldFinderOpts = DynFlags -> FinderOpts
initFinderOpts DynFlags
dflags
, ldUseByteCode :: Bool
ldUseByteCode = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_UseBytecodeRatherThanObjects DynFlags
dflags
, ldMsgOpts :: DiagnosticOpts IfaceMessage
ldMsgOpts = DynFlags -> DiagnosticOpts IfaceMessage
initIfaceMessageOpts DynFlags
dflags
, ldWays :: Ways
ldWays = DynFlags -> Ways
ways DynFlags
dflags
, SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)
ldLoadIface :: SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)
ldLoadIface :: SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)
ldLoadIface
, Module -> IO (Maybe Linkable)
ldLoadByteCode :: Module -> IO (Maybe Linkable)
ldLoadByteCode :: Module -> IO (Maybe Linkable)
ldLoadByteCode
}
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
ldLoadIface :: SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)
ldLoadIface SDoc
msg Module
mod = SDoc
-> HscEnv
-> IfG (MaybeErr MissingInterfaceError ModIface)
-> IO (MaybeErr MissingInterfaceError ModIface)
forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"loader") HscEnv
hsc_env
(IfG (MaybeErr MissingInterfaceError ModIface)
-> IO (MaybeErr MissingInterfaceError ModIface))
-> IfG (MaybeErr MissingInterfaceError ModIface)
-> IO (MaybeErr MissingInterfaceError ModIface)
forall a b. (a -> b) -> a -> b
$ SDoc
-> Module
-> WhereFrom
-> IfG (MaybeErr MissingInterfaceError ModIface)
forall lcl.
SDoc
-> Module
-> WhereFrom
-> IfM lcl (MaybeErr MissingInterfaceError ModIface)
loadInterface SDoc
msg Module
mod (IsBootInterface -> WhereFrom
ImportByUser IsBootInterface
NotBoot)
ldLoadByteCode :: Module -> IO (Maybe Linkable)
ldLoadByteCode Module
mod = do
EPS {eps_iface_bytecode} <- HscEnv -> IO ExternalPackageState
hscEPS HscEnv
hsc_env
sequence (lookupModuleEnv eps_iface_bytecode mod)
loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
loadDecls :: Interp
-> HscEnv
-> SrcSpan
-> Linkable
-> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
loadDecls Interp
interp HscEnv
hsc_env SrcSpan
span Linkable
linkable = do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
Interp
-> (LoaderState
-> IO
(LoaderState, ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)))
-> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
forall a. Interp -> (LoaderState -> IO (LoaderState, a)) -> IO a
modifyLoaderState Interp
interp ((LoaderState
-> IO
(LoaderState, ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)))
-> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded))
-> (LoaderState
-> IO
(LoaderState, ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)))
-> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls0 -> do
(pls1, objs_ok) <- Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadObjects Interp
interp HscEnv
hsc_env LoaderState
pls0 [Linkable
linkable]
when (failed objs_ok) $ throwGhcExceptionIO $ ProgramError "loadDecls: failed to load foreign objects"
(pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls1 span needed_mods
if failed ok
then throwGhcExceptionIO (ProgramError "")
else do
let le = LoaderState -> LinkerEnv
linker_env LoaderState
pls
le2 = LinkerEnv
le { itbl_env = foldl' (\ItblEnv
acc CompiledByteCode
cbc -> ItblEnv -> ItblEnv -> ItblEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv ItblEnv
acc (CompiledByteCode -> ItblEnv
bc_itbls CompiledByteCode
cbc)) (itbl_env le) cbcs
, addr_env = foldl' (\AddrEnv
acc CompiledByteCode
cbc -> AddrEnv -> AddrEnv -> AddrEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv AddrEnv
acc (CompiledByteCode -> AddrEnv
bc_strs CompiledByteCode
cbc)) (addr_env le) cbcs }
new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 cbcs
nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
let ce2 = ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv
extendClosureEnv (LinkerEnv -> ClosureEnv
closure_env LinkerEnv
le2) [(Name, ForeignHValue)]
nms_fhvs
!pls2 = LoaderState
pls { linker_env = le2 { closure_env = ce2 } }
return (pls2, (nms_fhvs, links_needed, units_needed))
where
cbcs :: [CompiledByteCode]
cbcs = Linkable -> [CompiledByteCode]
linkableBCOs Linkable
linkable
free_names :: [Name]
free_names = UniqDSet Name -> [Name]
forall a. UniqDSet a -> [a]
uniqDSetToList (UniqDSet Name -> [Name]) -> UniqDSet Name -> [Name]
forall a b. (a -> b) -> a -> b
$
(UniqDSet Name -> CompiledByteCode -> UniqDSet Name)
-> UniqDSet Name -> [CompiledByteCode] -> UniqDSet Name
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl'
(\UniqDSet Name
acc CompiledByteCode
cbc -> (UniqDSet Name -> UnlinkedBCO -> UniqDSet Name)
-> UniqDSet Name -> FlatBag UnlinkedBCO -> UniqDSet Name
forall b a. (b -> a -> b) -> b -> FlatBag a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\UniqDSet Name
acc' UnlinkedBCO
bco -> UnlinkedBCO -> UniqDSet Name
bcoFreeNames UnlinkedBCO
bco UniqDSet Name -> UniqDSet Name -> UniqDSet Name
forall a. UniqDSet a -> UniqDSet a -> UniqDSet a
`unionUniqDSets` UniqDSet Name
acc') UniqDSet Name
acc (CompiledByteCode -> FlatBag UnlinkedBCO
bc_bcos CompiledByteCode
cbc))
UniqDSet Name
forall a. UniqDSet a
emptyUniqDSet [CompiledByteCode]
cbcs
needed_mods :: [Module]
needed_mods :: [Module]
needed_mods = [ HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
n | Name
n <- [Name]
free_names,
Name -> Bool
isExternalName Name
n,
Bool -> Bool
not (Name -> Bool
isWiredInName Name
n)
]
loadModule :: Interp -> HscEnv -> Module -> IO ()
loadModule :: Interp -> HscEnv -> Module -> IO ()
loadModule Interp
interp HscEnv
hsc_env Module
mod = do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ Interp
interp ((LoaderState -> IO LoaderState) -> IO ())
-> (LoaderState -> IO LoaderState) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls -> do
(pls', ok, _, _) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls SrcSpan
noSrcSpan [Module
mod]
if failed ok
then throwGhcExceptionIO (ProgramError "could not load module")
else return pls'
loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
loadModuleLinkables :: Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadModuleLinkables Interp
interp HscEnv
hsc_env LoaderState
pls [Linkable]
linkables
= IO (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a. IO a -> IO a
mask_ (IO (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag))
-> IO (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a b. (a -> b) -> a -> b
$ do
Logger -> Int -> SDoc -> IO ()
debugTraceMsg (HscEnv -> Logger
hsc_logger HscEnv
hsc_env) Int
3 (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Loading module linkables") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Objects:") Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat (Linkable -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Linkable -> SDoc) -> [Linkable] -> [SDoc]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Linkable]
objs)),
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Bytecode:") Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat (Linkable -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Linkable -> SDoc) -> [Linkable] -> [SDoc]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Linkable]
bcos))
]
(pls1, ok_flag) <- Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadObjects Interp
interp HscEnv
hsc_env LoaderState
pls [Linkable]
objs
if failed ok_flag then
return (pls1, Failed)
else do
pls2 <- dynLinkBCOs interp pls1 bcos
return (pls2, Succeeded)
where
([Linkable]
objs, [Linkable]
bcos) = [Linkable] -> ([Linkable], [Linkable])
partitionLinkables [Linkable]
linkables
linkableInSet :: Linkable -> LinkableSet -> Bool
linkableInSet :: Linkable -> LinkableSet -> Bool
linkableInSet Linkable
l LinkableSet
objs_loaded =
case LinkableSet -> Module -> Maybe Linkable
forall a. ModuleEnv a -> Module -> Maybe a
lookupModuleEnv LinkableSet
objs_loaded (Linkable -> Module
linkableModule Linkable
l) of
Maybe Linkable
Nothing -> Bool
False
Just Linkable
m -> Linkable -> UTCTime
linkableTime Linkable
l UTCTime -> UTCTime -> Bool
forall a. Eq a => a -> a -> Bool
== Linkable -> UTCTime
linkableTime Linkable
m
loadObjects
:: Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadObjects :: Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadObjects Interp
interp HscEnv
hsc_env LoaderState
pls [Linkable]
objs = do
let (LinkableSet
objs_loaded', [Linkable]
new_objs) = LinkableSet -> [Linkable] -> (LinkableSet, [Linkable])
rmDupLinkables (LoaderState -> LinkableSet
objs_loaded LoaderState
pls) [Linkable]
objs
pls1 :: LoaderState
pls1 = LoaderState
pls { objs_loaded = objs_loaded' }
wanted_objs :: [String]
wanted_objs = (Linkable -> [String]) -> [Linkable] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Linkable -> [String]
linkableFiles [Linkable]
new_objs
if Interp -> Bool
interpreterDynamic Interp
interp
then do pls2 <- Interp -> HscEnv -> LoaderState -> [String] -> IO LoaderState
dynLoadObjs Interp
interp HscEnv
hsc_env LoaderState
pls1 [String]
wanted_objs
return (pls2, Succeeded)
else do (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> String -> IO ()
loadObj Interp
interp) [String]
wanted_objs
ok <- Interp -> IO SuccessFlag
resolveObjs Interp
interp
if succeeded ok then
return (pls1, Succeeded)
else do
pls2 <- unload_wkr interp [] pls1
return (pls2, Failed)
dynLoadObjs :: Interp -> HscEnv -> LoaderState -> [FilePath] -> IO LoaderState
dynLoadObjs :: Interp -> HscEnv -> LoaderState -> [String] -> IO LoaderState
dynLoadObjs Interp
_ HscEnv
_ LoaderState
pls [] = LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls
dynLoadObjs Interp
interp HscEnv
hsc_env pls :: LoaderState
pls@LoaderState{[(String, String)]
PkgsLoaded
LinkableSet
LinkerEnv
linker_env :: LoaderState -> LinkerEnv
pkgs_loaded :: LoaderState -> PkgsLoaded
bcos_loaded :: LoaderState -> LinkableSet
objs_loaded :: LoaderState -> LinkableSet
temp_sos :: LoaderState -> [(String, String)]
linker_env :: LinkerEnv
bcos_loaded :: LinkableSet
objs_loaded :: LinkableSet
pkgs_loaded :: PkgsLoaded
temp_sos :: [(String, String)]
..} [String]
objs = do
let unit_env :: UnitEnv
unit_env = HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
let tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
let platform :: Platform
platform = UnitEnv -> Platform
ue_platform UnitEnv
unit_env
let minus_ls :: [String]
minus_ls = [ String
lib | Option (Char
'-':Char
'l':String
lib) <- DynFlags -> [Option]
ldInputs DynFlags
dflags ]
let minus_big_ls :: [String]
minus_big_ls = [ String
lib | Option (Char
'-':Char
'L':String
lib) <- DynFlags -> [Option]
ldInputs DynFlags
dflags ]
(soFile, libPath , libName) <-
Logger
-> TmpFs
-> TempDir
-> TempFileLifetime
-> String
-> IO (String, String, String)
newTempLibName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
TFL_CurrentModule (Platform -> String
platformSOExt Platform
platform)
let
dflags2 = DynFlags
dflags {
ldInputs =
concatMap (\String
l -> [ String -> Option
Option (String
"-l" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l) ])
(nub $ snd <$> temp_sos)
++ concatMap (\String
lp -> String -> Option
Option (String
"-L" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lp)
Option -> [Option] -> [Option]
forall a. a -> [a] -> [a]
: if DynFlags -> OS -> Bool
useXLinkerRPath DynFlags
dflags (Platform -> OS
platformOS Platform
platform)
then [ String -> Option
Option String
"-Xlinker"
, String -> Option
Option String
"-rpath"
, String -> Option
Option String
"-Xlinker"
, String -> Option
Option String
lp ]
else [])
(nub $ fst <$> temp_sos)
++ concatMap
(\String
lp -> String -> Option
Option (String
"-L" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lp)
Option -> [Option] -> [Option]
forall a. a -> [a] -> [a]
: if DynFlags -> OS -> Bool
useXLinkerRPath DynFlags
dflags (Platform -> OS
platformOS Platform
platform)
then [ String -> Option
Option String
"-Xlinker"
, String -> Option
Option String
"-rpath"
, String -> Option
Option String
"-Xlinker"
, String -> Option
Option String
lp ]
else [])
minus_big_ls
++ map (\String
l -> String -> Option
Option (String
"-l" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l)) minus_ls,
targetWays_ = let ws = Way -> Ways
forall a. a -> Set a
Set.singleton Way
WayDyn
in if interpreterProfiled interp
then addWay WayProf ws
else ws,
outputFile_ = Just soFile
}
linkDynLib logger tmpfs dflags2 unit_env objs (loaded_pkg_uid <$> eltsUDFM pkgs_loaded)
changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
m <- loadDLL interp soFile
case m of
Right RemotePtr LoadedDLL
_ -> LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState -> IO LoaderState) -> LoaderState -> IO LoaderState
forall a b. (a -> b) -> a -> b
$! LoaderState
pls { temp_sos = (libPath, libName) : temp_sos }
Left String
err -> String -> String -> IO LoaderState
forall a. String -> String -> IO a
linkFail String
msg String
err
where
msg :: String
msg = String
"GHC.Linker.Loader.dynLoadObjs: Loading temp shared object failed"
rmDupLinkables :: LinkableSet
-> [Linkable]
-> (LinkableSet,
[Linkable])
rmDupLinkables :: LinkableSet -> [Linkable] -> (LinkableSet, [Linkable])
rmDupLinkables LinkableSet
already [Linkable]
ls
= LinkableSet
-> [Linkable] -> [Linkable] -> (LinkableSet, [Linkable])
go LinkableSet
already [] [Linkable]
ls
where
go :: LinkableSet
-> [Linkable] -> [Linkable] -> (LinkableSet, [Linkable])
go LinkableSet
already [Linkable]
extras [] = (LinkableSet
already, [Linkable]
extras)
go LinkableSet
already [Linkable]
extras (Linkable
l:[Linkable]
ls)
| Linkable -> LinkableSet -> Bool
linkableInSet Linkable
l LinkableSet
already = LinkableSet
-> [Linkable] -> [Linkable] -> (LinkableSet, [Linkable])
go LinkableSet
already [Linkable]
extras [Linkable]
ls
| Bool
otherwise = LinkableSet
-> [Linkable] -> [Linkable] -> (LinkableSet, [Linkable])
go (LinkableSet -> Module -> Linkable -> LinkableSet
forall a. ModuleEnv a -> Module -> a -> ModuleEnv a
extendModuleEnv LinkableSet
already (Linkable -> Module
linkableModule Linkable
l) Linkable
l) (Linkable
lLinkable -> [Linkable] -> [Linkable]
forall a. a -> [a] -> [a]
:[Linkable]
extras) [Linkable]
ls
dynLinkBCOs :: Interp -> LoaderState -> [Linkable] -> IO LoaderState
dynLinkBCOs :: Interp -> LoaderState -> [Linkable] -> IO LoaderState
dynLinkBCOs Interp
interp LoaderState
pls [Linkable]
bcos = do
let (LinkableSet
bcos_loaded', [Linkable]
new_bcos) = LinkableSet -> [Linkable] -> (LinkableSet, [Linkable])
rmDupLinkables (LoaderState -> LinkableSet
bcos_loaded LoaderState
pls) [Linkable]
bcos
pls1 :: LoaderState
pls1 = LoaderState
pls { bcos_loaded = bcos_loaded' }
parts :: [LinkablePart]
parts :: [LinkablePart]
parts = (Linkable -> [LinkablePart]) -> [Linkable] -> [LinkablePart]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (NonEmpty LinkablePart -> [LinkablePart]
forall a. NonEmpty a -> [a]
NE.toList (NonEmpty LinkablePart -> [LinkablePart])
-> (Linkable -> NonEmpty LinkablePart)
-> Linkable
-> [LinkablePart]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Linkable -> NonEmpty LinkablePart
linkableParts) [Linkable]
new_bcos
cbcs :: [CompiledByteCode]
cbcs :: [CompiledByteCode]
cbcs = (LinkablePart -> [CompiledByteCode])
-> [LinkablePart] -> [CompiledByteCode]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LinkablePart -> [CompiledByteCode]
linkablePartAllBCOs [LinkablePart]
parts
le1 :: LinkerEnv
le1 = LoaderState -> LinkerEnv
linker_env LoaderState
pls
ie2 :: ItblEnv
ie2 = (ItblEnv -> ItblEnv -> ItblEnv) -> ItblEnv -> [ItblEnv] -> ItblEnv
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ItblEnv -> ItblEnv -> ItblEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv (LinkerEnv -> ItblEnv
itbl_env LinkerEnv
le1) ((CompiledByteCode -> ItblEnv) -> [CompiledByteCode] -> [ItblEnv]
forall a b. (a -> b) -> [a] -> [b]
map CompiledByteCode -> ItblEnv
bc_itbls [CompiledByteCode]
cbcs)
ae2 :: AddrEnv
ae2 = (AddrEnv -> AddrEnv -> AddrEnv) -> AddrEnv -> [AddrEnv] -> AddrEnv
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr AddrEnv -> AddrEnv -> AddrEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv (LinkerEnv -> AddrEnv
addr_env LinkerEnv
le1) ((CompiledByteCode -> AddrEnv) -> [CompiledByteCode] -> [AddrEnv]
forall a b. (a -> b) -> [a] -> [b]
map CompiledByteCode -> AddrEnv
bc_strs [CompiledByteCode]
cbcs)
le2 :: LinkerEnv
le2 = LinkerEnv
le1 { itbl_env = ie2, addr_env = ae2 }
names_and_refs <- Interp
-> PkgsLoaded
-> LinkerEnv
-> [CompiledByteCode]
-> IO [(Name, HValueRef)]
linkSomeBCOs Interp
interp (LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls) LinkerEnv
le2 [CompiledByteCode]
cbcs
let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
freeHValueRefs interp (map snd to_drop)
new_binds <- makeForeignNamedHValueRefs interp to_add
let ce2 = ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv
extendClosureEnv (LinkerEnv -> ClosureEnv
closure_env LinkerEnv
le2) [(Name, ForeignHValue)]
new_binds
return $! pls1 { linker_env = le2 { closure_env = ce2 } }
linkSomeBCOs :: Interp
-> PkgsLoaded
-> LinkerEnv
-> [CompiledByteCode]
-> IO [(Name,HValueRef)]
linkSomeBCOs :: Interp
-> PkgsLoaded
-> LinkerEnv
-> [CompiledByteCode]
-> IO [(Name, HValueRef)]
linkSomeBCOs Interp
interp PkgsLoaded
pkgs_loaded LinkerEnv
le [CompiledByteCode]
mods = (CompiledByteCode
-> ([[UnlinkedBCO]] -> IO [(Name, HValueRef)])
-> [[UnlinkedBCO]]
-> IO [(Name, HValueRef)])
-> ([[UnlinkedBCO]] -> IO [(Name, HValueRef)])
-> [CompiledByteCode]
-> [[UnlinkedBCO]]
-> IO [(Name, HValueRef)]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr CompiledByteCode
-> ([[UnlinkedBCO]] -> IO [(Name, HValueRef)])
-> [[UnlinkedBCO]]
-> IO [(Name, HValueRef)]
forall {t}.
CompiledByteCode -> ([[UnlinkedBCO]] -> t) -> [[UnlinkedBCO]] -> t
fun [[UnlinkedBCO]] -> IO [(Name, HValueRef)]
do_link [CompiledByteCode]
mods []
where
fun :: CompiledByteCode -> ([[UnlinkedBCO]] -> t) -> [[UnlinkedBCO]] -> t
fun CompiledByteCode{[SptEntry]
[FFIInfo]
Maybe ModBreaks
AddrEnv
ItblEnv
FlatBag UnlinkedBCO
bc_itbls :: CompiledByteCode -> ItblEnv
bc_strs :: CompiledByteCode -> AddrEnv
bc_bcos :: CompiledByteCode -> FlatBag UnlinkedBCO
bc_bcos :: FlatBag UnlinkedBCO
bc_itbls :: ItblEnv
bc_ffis :: [FFIInfo]
bc_strs :: AddrEnv
bc_breaks :: Maybe ModBreaks
bc_spt_entries :: [SptEntry]
bc_spt_entries :: CompiledByteCode -> [SptEntry]
bc_breaks :: CompiledByteCode -> Maybe ModBreaks
bc_ffis :: CompiledByteCode -> [FFIInfo]
..} [[UnlinkedBCO]] -> t
inner [[UnlinkedBCO]]
accum =
[[UnlinkedBCO]] -> t
inner (FlatBag UnlinkedBCO -> [UnlinkedBCO]
forall a. FlatBag a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList FlatBag UnlinkedBCO
bc_bcos [UnlinkedBCO] -> [[UnlinkedBCO]] -> [[UnlinkedBCO]]
forall a. a -> [a] -> [a]
: [[UnlinkedBCO]]
accum)
do_link :: [[UnlinkedBCO]] -> IO [(Name, HValueRef)]
do_link [] = [(Name, HValueRef)] -> IO [(Name, HValueRef)]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
do_link [[UnlinkedBCO]]
mods = do
let flat :: [UnlinkedBCO]
flat = [ UnlinkedBCO
bco | [UnlinkedBCO]
bcos <- [[UnlinkedBCO]]
mods, UnlinkedBCO
bco <- [UnlinkedBCO]
bcos ]
names :: [Name]
names = (UnlinkedBCO -> Name) -> [UnlinkedBCO] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map UnlinkedBCO -> Name
unlinkedBCOName [UnlinkedBCO]
flat
bco_ix :: NameEnv Int
bco_ix = [(Name, Int)] -> NameEnv Int
forall a. [(Name, a)] -> NameEnv a
mkNameEnv ([Name] -> [Int] -> [(Name, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
names [Int
0..])
resolved <- [IO ResolvedBCO] -> IO [ResolvedBCO]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [ Interp
-> PkgsLoaded
-> LinkerEnv
-> NameEnv Int
-> UnlinkedBCO
-> IO ResolvedBCO
linkBCO Interp
interp PkgsLoaded
pkgs_loaded LinkerEnv
le NameEnv Int
bco_ix UnlinkedBCO
bco | UnlinkedBCO
bco <- [UnlinkedBCO]
flat ]
hvrefs <- createBCOs interp resolved
return (zip names hvrefs)
makeForeignNamedHValueRefs
:: Interp -> [(Name,HValueRef)] -> IO [(Name,ForeignHValue)]
makeForeignNamedHValueRefs :: Interp -> [(Name, HValueRef)] -> IO [(Name, ForeignHValue)]
makeForeignNamedHValueRefs Interp
interp [(Name, HValueRef)]
bindings =
((Name, HValueRef) -> IO (Name, ForeignHValue))
-> [(Name, HValueRef)] -> IO [(Name, ForeignHValue)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(Name
n, HValueRef
hvref) -> (Name
n,) (ForeignHValue -> (Name, ForeignHValue))
-> IO ForeignHValue -> IO (Name, ForeignHValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Interp -> HValueRef -> IO ForeignHValue
forall a. Interp -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue Interp
interp HValueRef
hvref) [(Name, HValueRef)]
bindings
unload
:: Interp
-> HscEnv
-> [Linkable]
-> IO ()
unload :: Interp -> HscEnv -> [Linkable] -> IO ()
unload Interp
interp HscEnv
hsc_env [Linkable]
linkables
= IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
new_pls
<- Interp
-> (LoaderState -> IO (LoaderState, LoaderState)) -> IO LoaderState
forall a. Interp -> (LoaderState -> IO (LoaderState, a)) -> IO a
modifyLoaderState Interp
interp ((LoaderState -> IO (LoaderState, LoaderState)) -> IO LoaderState)
-> (LoaderState -> IO (LoaderState, LoaderState)) -> IO LoaderState
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls -> do
pls1 <- Interp -> [Linkable] -> LoaderState -> IO LoaderState
unload_wkr Interp
interp [Linkable]
linkables LoaderState
pls
return (pls1, pls1)
let logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
debugTraceMsg logger 3 $
text "unload: retaining objs" <+> ppr (moduleEnvElts $ objs_loaded new_pls)
debugTraceMsg logger 3 $
text "unload: retaining bcos" <+> ppr (moduleEnvElts $ bcos_loaded new_pls)
return ()
unload_wkr
:: Interp
-> [Linkable]
-> LoaderState
-> IO LoaderState
unload_wkr :: Interp -> [Linkable] -> LoaderState -> IO LoaderState
unload_wkr Interp
interp [Linkable]
keep_linkables pls :: LoaderState
pls@LoaderState{[(String, String)]
PkgsLoaded
LinkableSet
LinkerEnv
linker_env :: LoaderState -> LinkerEnv
pkgs_loaded :: LoaderState -> PkgsLoaded
bcos_loaded :: LoaderState -> LinkableSet
objs_loaded :: LoaderState -> LinkableSet
temp_sos :: LoaderState -> [(String, String)]
linker_env :: LinkerEnv
bcos_loaded :: LinkableSet
objs_loaded :: LinkableSet
pkgs_loaded :: PkgsLoaded
temp_sos :: [(String, String)]
..} = do
let ([Linkable]
objs_to_keep', [Linkable]
bcos_to_keep') = (Linkable -> Bool) -> [Linkable] -> ([Linkable], [Linkable])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Linkable -> Bool
linkableIsNativeCodeOnly [Linkable]
keep_linkables
objs_to_keep :: LinkableSet
objs_to_keep = [Linkable] -> LinkableSet
mkLinkableSet [Linkable]
objs_to_keep'
bcos_to_keep :: LinkableSet
bcos_to_keep = [Linkable] -> LinkableSet
mkLinkableSet [Linkable]
bcos_to_keep'
discard :: LinkableSet -> Linkable -> Bool
discard LinkableSet
keep Linkable
l = Bool -> Bool
not (Linkable -> LinkableSet -> Bool
linkableInSet Linkable
l LinkableSet
keep)
(LinkableSet
objs_to_unload, LinkableSet
remaining_objs_loaded) =
(Linkable -> Bool) -> LinkableSet -> (LinkableSet, LinkableSet)
forall a. (a -> Bool) -> ModuleEnv a -> (ModuleEnv a, ModuleEnv a)
partitionModuleEnv (LinkableSet -> Linkable -> Bool
discard LinkableSet
objs_to_keep) LinkableSet
objs_loaded
(LinkableSet
bcos_to_unload, LinkableSet
remaining_bcos_loaded) =
(Linkable -> Bool) -> LinkableSet -> (LinkableSet, LinkableSet)
forall a. (a -> Bool) -> ModuleEnv a -> (ModuleEnv a, ModuleEnv a)
partitionModuleEnv (LinkableSet -> Linkable -> Bool
discard LinkableSet
bcos_to_keep) LinkableSet
bcos_loaded
linkables_to_unload :: [Linkable]
linkables_to_unload = LinkableSet -> [Linkable]
forall a. ModuleEnv a -> [a]
moduleEnvElts LinkableSet
objs_to_unload [Linkable] -> [Linkable] -> [Linkable]
forall a. [a] -> [a] -> [a]
++ LinkableSet -> [Linkable]
forall a. ModuleEnv a -> [a]
moduleEnvElts LinkableSet
bcos_to_unload
(Linkable -> IO ()) -> [Linkable] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Linkable -> IO ()
unloadObjs [Linkable]
linkables_to_unload
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not ([Linkable] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ((Linkable -> Bool) -> [Linkable] -> [Linkable]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Linkable -> Bool) -> Linkable -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> Bool) -> (Linkable -> [String]) -> Linkable -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Linkable -> [String]
linkableObjs) [Linkable]
linkables_to_unload))) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Interp -> IO ()
purgeLookupSymbolCache Interp
interp
let
keep_name :: Name -> Bool
keep_name :: Name -> Bool
keep_name Name
n = Name -> Bool
isExternalName Name
n Bool -> Bool -> Bool
&&
HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
n Module -> LinkableSet -> Bool
forall a. Module -> ModuleEnv a -> Bool
`elemModuleEnv` LinkableSet
remaining_bcos_loaded
!new_pls :: LoaderState
new_pls = LoaderState
pls { linker_env = filterLinkerEnv keep_name linker_env,
bcos_loaded = remaining_bcos_loaded,
objs_loaded = remaining_objs_loaded }
LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
new_pls
where
unloadObjs :: Linkable -> IO ()
unloadObjs :: Linkable -> IO ()
unloadObjs Linkable
lnk
| Interp -> Bool
interpreterDynamic Interp
interp = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> String -> IO ()
unloadObj Interp
interp) (Linkable -> [String]
linkableObjs Linkable
lnk)
showLS :: LibrarySpec -> String
showLS :: LibrarySpec -> String
showLS (Objects [String]
nms) = String
"(static) [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
nms String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
showLS (Archive String
nm) = String
"(static archive) " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
showLS (DLL String
nm) = String
"(dynamic) " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
showLS (DLLPath String
nm) = String
"(dynamic) " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
showLS (Framework String
nm) = String
"(framework) " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
loadPackages :: Interp -> HscEnv -> [UnitId] -> IO ()
loadPackages :: Interp -> HscEnv -> [UnitId] -> IO ()
loadPackages Interp
interp HscEnv
hsc_env [UnitId]
new_pkgs = do
Interp -> HscEnv -> IO ()
initLoaderState Interp
interp HscEnv
hsc_env
Interp -> (LoaderState -> IO LoaderState) -> IO ()
modifyLoaderState_ Interp
interp ((LoaderState -> IO LoaderState) -> IO ())
-> (LoaderState -> IO LoaderState) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LoaderState
pls ->
Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' Interp
interp HscEnv
hsc_env [UnitId]
new_pkgs LoaderState
pls
loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' Interp
interp HscEnv
hsc_env [UnitId]
new_pks LoaderState
pls = do
pkgs' <- PkgsLoaded -> [UnitId] -> IO PkgsLoaded
link (LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls) [UnitId]
new_pks
return $! pls { pkgs_loaded = pkgs'
}
where
link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
link PkgsLoaded
pkgs [UnitId]
new_pkgs =
(PkgsLoaded -> UnitId -> IO PkgsLoaded)
-> PkgsLoaded -> [UnitId] -> IO PkgsLoaded
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM PkgsLoaded -> UnitId -> IO PkgsLoaded
link_one PkgsLoaded
pkgs [UnitId]
new_pkgs
link_one :: PkgsLoaded -> UnitId -> IO PkgsLoaded
link_one PkgsLoaded
pkgs UnitId
new_pkg
| UnitId
new_pkg UnitId -> PkgsLoaded -> Bool
forall key elt. Uniquable key => key -> UniqDFM key elt -> Bool
`elemUDFM` PkgsLoaded
pkgs
= PkgsLoaded -> IO PkgsLoaded
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PkgsLoaded
pkgs
| Just UnitInfo
pkg_cfg <- UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId (HasDebugCallStack => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units HscEnv
hsc_env) UnitId
new_pkg
= do { let deps :: [UnitId]
deps = UnitInfo -> [UnitId]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> [uid]
unitDepends UnitInfo
pkg_cfg
; pkgs' <- PkgsLoaded -> [UnitId] -> IO PkgsLoaded
link PkgsLoaded
pkgs [UnitId]
deps
; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
; let trans_deps = [UniqDSet UnitId] -> UniqDSet UnitId
forall a. [UniqDSet a] -> UniqDSet a
unionManyUniqDSets [ UniqDSet UnitId -> UnitId -> UniqDSet UnitId
forall a. Uniquable a => UniqDSet a -> a -> UniqDSet a
addOneToUniqDSet (LoadedPkgInfo -> UniqDSet UnitId
loaded_pkg_trans_deps LoadedPkgInfo
loaded_pkg_info) UnitId
dep_pkg
| UnitId
dep_pkg <- [UnitId]
deps
, Just LoadedPkgInfo
loaded_pkg_info <- Maybe LoadedPkgInfo -> [Maybe LoadedPkgInfo]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PkgsLoaded -> UnitId -> Maybe LoadedPkgInfo
forall key elt.
Uniquable key =>
UniqDFM key elt -> key -> Maybe elt
lookupUDFM PkgsLoaded
pkgs' UnitId
dep_pkg)
]
; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
| Bool
otherwise
= GhcException -> IO PkgsLoaded
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
CmdLineError (String
"unknown package: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FastString -> String
unpackFS (UnitId -> FastString
unitIdFS UnitId
new_pkg)))
loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
loadPackage :: Interp
-> HscEnv
-> UnitInfo
-> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
loadPackage Interp
interp HscEnv
hsc_env UnitInfo
pkg
= do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
is_dyn :: Bool
is_dyn = Interp -> Bool
interpreterDynamic Interp
interp
dirs :: [String]
dirs | Bool
is_dyn = (FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack ([FilePathST] -> [String]) -> [FilePathST] -> [String]
forall a b. (a -> b) -> a -> b
$ UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitLibraryDynDirs UnitInfo
pkg
| Bool
otherwise = (FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack ([FilePathST] -> [String]) -> [FilePathST] -> [String]
forall a b. (a -> b) -> a -> b
$ UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitLibraryDirs UnitInfo
pkg
let hs_libs :: [String]
hs_libs = (FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack ([FilePathST] -> [String]) -> [FilePathST] -> [String]
forall a b. (a -> b) -> a -> b
$ UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitLibraries UnitInfo
pkg
hs_libs' :: [String]
hs_libs' = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String
"HSffi" String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/=) [String]
hs_libs
extdeplibs :: [String]
extdeplibs = (FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack (if [FilePathST] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitExtDepLibsGhc UnitInfo
pkg)
then UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitExtDepLibsSys UnitInfo
pkg
else UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitExtDepLibsGhc UnitInfo
pkg)
linkerlibs :: [String]
linkerlibs = [ String
lib | Char
'-':Char
'l':String
lib <- ((FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack ([FilePathST] -> [String]) -> [FilePathST] -> [String]
forall a b. (a -> b) -> a -> b
$ UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitLinkerOptions UnitInfo
pkg) ]
extra_libs :: [String]
extra_libs = [String]
extdeplibs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
linkerlibs
gcc_paths <- Logger -> DynFlags -> OS -> IO [String]
getGCCPaths Logger
logger DynFlags
dflags (Platform -> OS
platformOS Platform
platform)
dirs_env <- addEnvPaths "LIBRARY_PATH" dirs
hs_classifieds
<- mapM (locateLib interp hsc_env True dirs_env gcc_paths) hs_libs'
extra_classifieds
<- mapM (locateLib interp hsc_env False dirs_env gcc_paths) extra_libs
let classifieds = [LibrarySpec]
hs_classifieds [LibrarySpec] -> [LibrarySpec] -> [LibrarySpec]
forall a. [a] -> [a] -> [a]
++ [LibrarySpec]
extra_classifieds
let known_hs_dlls = [ String
dll | DLLPath String
dll <- [LibrarySpec]
hs_classifieds ]
known_extra_dlls = [ String
dll | DLLPath String
dll <- [LibrarySpec]
extra_classifieds ]
known_dlls = [String]
known_hs_dlls [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
known_extra_dlls
#if defined(CAN_LOAD_DLL)
dlls = [ String
dll | DLL String
dll <- [LibrarySpec]
classifieds ]
#endif
objs = [ String
obj | Objects [String]
objs <- [LibrarySpec]
classifieds
, String
obj <- [String]
objs ]
archs = [ String
arch | Archive String
arch <- [LibrarySpec]
classifieds ]
let dll_paths = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
takeDirectory [String]
known_dlls
all_paths = [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
normalise ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
dll_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
dirs
all_paths_env <- addEnvPaths "LD_LIBRARY_PATH" all_paths
pathCache <- mapM (addLibrarySearchPath interp) all_paths_env
maybePutSDoc logger
(text "Loading unit " <> pprUnitInfoForUser pkg <> text " ... ")
#if defined(CAN_LOAD_DLL)
loadFrameworks interp platform pkg
mapM_ (load_dyn interp hsc_env True) known_extra_dlls
loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
#else
let loaded_dlls = []
#endif
mapM_ (loadObj interp) objs
mapM_ (loadArchive interp) archs
maybePutStr logger "linking ... "
ok <- resolveObjs interp
mapM_ (removeLibrarySearchPath interp) $ reverse pathCache
if succeeded ok
then do
maybePutStrLn logger "done."
return (hs_classifieds, extra_classifieds, loaded_dlls)
else let errmsg = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"unable to load unit `"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> UnitInfo -> SDoc
pprUnitInfoForUser UnitInfo
pkg SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"'"
in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
#if defined(CAN_LOAD_DLL)
load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
load_dyn :: Interp
-> HscEnv -> Bool -> String -> IO (Maybe (RemotePtr LoadedDLL))
load_dyn Interp
interp HscEnv
hsc_env Bool
crash_early String
dll = do
r <- Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
loadDLL Interp
interp String
dll
case r of
Right RemotePtr LoadedDLL
loaded_dll -> Maybe (RemotePtr LoadedDLL) -> IO (Maybe (RemotePtr LoadedDLL))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RemotePtr LoadedDLL -> Maybe (RemotePtr LoadedDLL)
forall a. a -> Maybe a
Just RemotePtr LoadedDLL
loaded_dll)
Left String
err ->
if Bool
crash_early
then String -> IO (Maybe (RemotePtr LoadedDLL))
forall a. String -> IO a
cmdLineErrorIO String
err
else do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (WarningFlag -> DiagOpts -> Bool
diag_wopt WarningFlag
Opt_WarnMissedExtraSharedLib DiagOpts
diag_opts)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg Logger
logger
(DiagOpts
-> DiagnosticReason -> Maybe DiagnosticCode -> MessageClass
mkMCDiagnostic DiagOpts
diag_opts (WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnMissedExtraSharedLib) Maybe DiagnosticCode
forall a. Maybe a
Nothing)
SrcSpan
noSrcSpan (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle (String -> SDoc
forall {b}. (IsDoc b, IsLine b) => String -> b
note String
err)
Maybe (RemotePtr LoadedDLL) -> IO (Maybe (RemotePtr LoadedDLL))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (RemotePtr LoadedDLL)
forall a. Maybe a
Nothing
where
diag_opts :: DiagOpts
diag_opts = DynFlags -> DiagOpts
initDiagOpts (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
note :: String -> b
note String
err = [b] -> b
forall doc. IsDoc doc => [doc] -> doc
vcat ([b] -> b) -> [b] -> b
forall a b. (a -> b) -> a -> b
$ (String -> b) -> [String] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map String -> b
forall doc. IsLine doc => String -> doc
text
[ String
err
, String
"It's OK if you don't want to use symbols from it directly."
, String
"(the package DLL is loaded by the system linker"
, String
" which manages dependencies by itself)." ]
loadFrameworks :: Interp -> Platform -> UnitInfo -> IO ()
loadFrameworks :: Interp -> Platform -> UnitInfo -> IO ()
loadFrameworks Interp
interp Platform
platform UnitInfo
pkg
= Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Platform -> Bool
platformUsesFrameworks Platform
platform) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
load [String]
frameworks
where
fw_dirs :: [String]
fw_dirs = (FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack ([FilePathST] -> [String]) -> [FilePathST] -> [String]
forall a b. (a -> b) -> a -> b
$ UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitExtDepFrameworkDirs UnitInfo
pkg
frameworks :: [String]
frameworks = (FilePathST -> String) -> [FilePathST] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FilePathST -> String
ST.unpack ([FilePathST] -> [String]) -> [FilePathST] -> [String]
forall a b. (a -> b) -> a -> b
$ UnitInfo -> [FilePathST]
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [FilePathST]
Packages.unitExtDepFrameworks UnitInfo
pkg
load :: String -> IO ()
load String
fw = do r <- Interp -> [String] -> String -> IO (Maybe String)
loadFramework Interp
interp [String]
fw_dirs String
fw
case r of
Maybe String
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just String
err -> String -> IO ()
forall a. String -> IO a
cmdLineErrorIO (String
"can't load framework: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fw String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
err String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")" )
#endif
locateLib
:: Interp
-> HscEnv
-> Bool
-> [FilePath]
-> [FilePath]
-> String
-> IO LibrarySpec
locateLib :: Interp
-> HscEnv
-> Bool
-> [String]
-> [String]
-> String
-> IO LibrarySpec
locateLib Interp
interp HscEnv
hsc_env Bool
is_hs [String]
lib_dirs [String]
gcc_dirs String
lib0
| Bool -> Bool
not Bool
is_hs
=
#if defined(CAN_LOAD_DLL)
Bool -> IO (Maybe LibrarySpec)
findDll Bool
user IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
#endif
Bool -> IO (Maybe LibrarySpec)
tryImpLib Bool
user IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
#if defined(CAN_LOAD_DLL)
Bool -> IO (Maybe LibrarySpec)
findDll Bool
gcc IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO (Maybe LibrarySpec)
findSysDll IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
#endif
Bool -> IO (Maybe LibrarySpec)
tryImpLib Bool
gcc IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO (Maybe LibrarySpec)
findArchive IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO (Maybe LibrarySpec)
tryGcc IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO LibrarySpec
assumeDll
| Bool
loading_dynamic_hs_libs
= IO (Maybe LibrarySpec)
findHSDll IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO (Maybe LibrarySpec)
findDynObject IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO LibrarySpec
assumeDll
| Bool
otherwise
= IO (Maybe LibrarySpec)
findObject IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO (Maybe LibrarySpec)
findArchive IO (Maybe LibrarySpec) -> IO LibrarySpec -> IO LibrarySpec
forall {m :: * -> *} {b}. Monad m => m (Maybe b) -> m b -> m b
`orElse`
IO LibrarySpec
assumeDll
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
diag_opts :: DiagOpts
diag_opts = DynFlags -> DiagOpts
initDiagOpts DynFlags
dflags
dirs :: [String]
dirs = [String]
lib_dirs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
gcc_dirs
gcc :: Bool
gcc = Bool
False
user :: Bool
user = Bool
True
(String
lib, Bool
verbatim) = case String
lib0 of
Char
':' : String
rest -> (String
rest, Bool
True)
String
other -> (String
other, Bool
False)
obj_file :: String
obj_file
| Bool
is_hs Bool -> Bool -> Bool
&& Bool
loading_profiled_hs_libs = String
lib String -> String -> String
<.> String
"p_o"
| Bool
otherwise = String
lib String -> String -> String
<.> String
"o"
dyn_obj_file :: String
dyn_obj_file = String
lib String -> String -> String
<.> String
"dyn_o"
arch_files :: [String]
arch_files
| Bool
verbatim = [String
lib]
| Bool
otherwise = [ String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib_tag String -> String -> String
<.> String
"a"
, String
lib String -> String -> String
<.> String
"a"
, String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib
, String
lib
]
lib_tag :: String
lib_tag = if Bool
is_hs Bool -> Bool -> Bool
&& Bool
loading_profiled_hs_libs then String
"_p" else String
""
loading_profiled_hs_libs :: Bool
loading_profiled_hs_libs = Interp -> Bool
interpreterProfiled Interp
interp
loading_dynamic_hs_libs :: Bool
loading_dynamic_hs_libs = Interp -> Bool
interpreterDynamic Interp
interp
import_libs :: [String]
import_libs
| Bool
verbatim = [String
lib]
| Bool
otherwise = [ String
lib String -> String -> String
<.> String
"lib"
, String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib String -> String -> String
<.> String
"lib"
, String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib String -> String -> String
<.> String
"dll.a"
, String
lib String -> String -> String
<.> String
"dll.a"
]
hs_dyn_lib_name :: String
hs_dyn_lib_name = String
lib String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib_tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ GhcNameVersion -> String
dynLibSuffix (DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags)
hs_dyn_lib_file :: String
hs_dyn_lib_file = Platform -> String -> String
platformHsSOName Platform
platform String
hs_dyn_lib_name
#if defined(CAN_LOAD_DLL)
so_name :: String
so_name = Platform -> String -> String
platformSOName Platform
platform String
lib
lib_so_name :: String
lib_so_name = String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
so_name
dyn_lib_file :: String
dyn_lib_file
| Bool
verbatim Bool -> Bool -> Bool
&& (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
`isExtensionOf` String
lib) [String
".so", String
".dylib", String
".dll"]
= String
lib
| Arch
ArchX86_64 <- Arch
arch
, OS
OSSolaris2 <- OS
os
= String
"64" String -> String -> String
</> String
so_name
| Bool
otherwise
= String
so_name
#endif
findObject :: IO (Maybe LibrarySpec)
findObject = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec)
-> (String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> a -> b
$ [String] -> LibrarySpec
Objects ([String] -> LibrarySpec)
-> (String -> [String]) -> String -> LibrarySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[])) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ [String] -> String -> IO (Maybe String)
findFile [String]
dirs String
obj_file
findDynObject :: IO (Maybe LibrarySpec)
findDynObject = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec)
-> (String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> a -> b
$ [String] -> LibrarySpec
Objects ([String] -> LibrarySpec)
-> (String -> [String]) -> String -> LibrarySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[])) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ [String] -> String -> IO (Maybe String)
findFile [String]
dirs String
dyn_obj_file
findArchive :: IO (Maybe LibrarySpec)
findArchive = let local :: String -> IO (Maybe LibrarySpec)
local String
name = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> LibrarySpec
Archive) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ [String] -> String -> IO (Maybe String)
findFile [String]
dirs String
name
in [IO (Maybe LibrarySpec)] -> IO (Maybe LibrarySpec)
forall a. [IO (Maybe a)] -> IO (Maybe a)
apply ((String -> IO (Maybe LibrarySpec))
-> [String] -> [IO (Maybe LibrarySpec)]
forall a b. (a -> b) -> [a] -> [b]
map String -> IO (Maybe LibrarySpec)
local [String]
arch_files)
findHSDll :: IO (Maybe LibrarySpec)
findHSDll = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> LibrarySpec
DLLPath) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ [String] -> String -> IO (Maybe String)
findFile [String]
dirs String
hs_dyn_lib_file
#if defined(CAN_LOAD_DLL)
findDll :: Bool -> IO (Maybe LibrarySpec)
findDll Bool
re = let dirs' :: [String]
dirs' = if Bool
re Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
user then [String]
lib_dirs else [String]
gcc_dirs
in (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> LibrarySpec
DLLPath) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ [String] -> String -> IO (Maybe String)
findFile [String]
dirs' String
dyn_lib_file
findSysDll :: IO (Maybe LibrarySpec)
findSysDll = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec)
-> (String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> a -> b
$ String -> LibrarySpec
DLL (String -> LibrarySpec)
-> (String -> String) -> String -> LibrarySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
dropExtension (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
takeFileName) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$
Interp -> String -> IO (Maybe String)
findSystemLibrary Interp
interp String
so_name
#endif
tryGcc :: IO (Maybe LibrarySpec)
tryGcc = let search :: String -> [String] -> IO (Maybe String)
search = Logger -> DynFlags -> String -> [String] -> IO (Maybe String)
searchForLibUsingGcc Logger
logger DynFlags
dflags
#if defined(CAN_LOAD_DLL)
dllpath :: IO (Maybe String) -> IO (Maybe LibrarySpec)
dllpath = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> LibrarySpec
DLLPath)
short :: IO (Maybe LibrarySpec)
short = IO (Maybe String) -> IO (Maybe LibrarySpec)
dllpath (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO (Maybe String)
search String
so_name [String]
lib_dirs
full :: IO (Maybe LibrarySpec)
full = IO (Maybe String) -> IO (Maybe LibrarySpec)
dllpath (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO (Maybe String)
search String
lib_so_name [String]
lib_dirs
dlls :: [IO (Maybe LibrarySpec)]
dlls = [IO (Maybe LibrarySpec)
short, IO (Maybe LibrarySpec)
full]
#endif
gcc :: String -> IO (Maybe LibrarySpec)
gcc String
name = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> LibrarySpec
Archive) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO (Maybe String)
search String
name [String]
lib_dirs
files :: [String]
files = [String]
import_libs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
arch_files
archives :: [IO (Maybe LibrarySpec)]
archives = (String -> IO (Maybe LibrarySpec))
-> [String] -> [IO (Maybe LibrarySpec)]
forall a b. (a -> b) -> [a] -> [b]
map String -> IO (Maybe LibrarySpec)
gcc [String]
files
in [IO (Maybe LibrarySpec)] -> IO (Maybe LibrarySpec)
forall a. [IO (Maybe a)] -> IO (Maybe a)
apply ([IO (Maybe LibrarySpec)] -> IO (Maybe LibrarySpec))
-> [IO (Maybe LibrarySpec)] -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$
#if defined(CAN_LOAD_DLL)
[IO (Maybe LibrarySpec)]
dlls [IO (Maybe LibrarySpec)]
-> [IO (Maybe LibrarySpec)] -> [IO (Maybe LibrarySpec)]
forall a. [a] -> [a] -> [a]
++
#endif
[IO (Maybe LibrarySpec)]
archives
tryImpLib :: Bool -> IO (Maybe LibrarySpec)
tryImpLib Bool
re = case OS
os of
OS
OSMinGW32 ->
let dirs' :: [String]
dirs' = if Bool
re Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
user then [String]
lib_dirs else [String]
gcc_dirs
implib :: String -> IO (Maybe LibrarySpec)
implib String
name = (Maybe String -> Maybe LibrarySpec)
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((String -> LibrarySpec) -> Maybe String -> Maybe LibrarySpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> LibrarySpec
Archive) (IO (Maybe String) -> IO (Maybe LibrarySpec))
-> IO (Maybe String) -> IO (Maybe LibrarySpec)
forall a b. (a -> b) -> a -> b
$
[String] -> String -> IO (Maybe String)
findFile [String]
dirs' String
name
in [IO (Maybe LibrarySpec)] -> IO (Maybe LibrarySpec)
forall a. [IO (Maybe a)] -> IO (Maybe a)
apply ((String -> IO (Maybe LibrarySpec))
-> [String] -> [IO (Maybe LibrarySpec)]
forall a b. (a -> b) -> [a] -> [b]
map String -> IO (Maybe LibrarySpec)
implib [String]
import_libs)
OS
_ -> Maybe LibrarySpec -> IO (Maybe LibrarySpec)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LibrarySpec
forall a. Maybe a
Nothing
assumeDll :: IO LibrarySpec
assumeDll
| Bool
is_hs
, Bool -> Bool
not Bool
loading_dynamic_hs_libs
, Interp -> Bool
interpreterProfiled Interp
interp
= do
let diag :: MessageClass
diag = DiagOpts
-> DiagnosticReason -> Maybe DiagnosticCode -> MessageClass
mkMCDiagnostic DiagOpts
diag_opts DiagnosticReason
WarningWithoutFlag Maybe DiagnosticCode
forall a. Maybe a
Nothing
Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg Logger
logger MessageClass
diag SrcSpan
noSrcSpan (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultErrStyle (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Interpreter failed to load profiled static library" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
lib SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'.' SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" \tTrying dynamic library instead. If this fails try to rebuild" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"libraries with profiling support."
LibrarySpec -> IO LibrarySpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> LibrarySpec
DLL String
lib)
| Bool
otherwise = LibrarySpec -> IO LibrarySpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> LibrarySpec
DLL String
lib)
infixr `orElse`
m (Maybe b)
f orElse :: m (Maybe b) -> m b -> m b
`orElse` m b
g = m (Maybe b)
f m (Maybe b) -> (Maybe b -> m b) -> m b
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= m b -> (b -> m b) -> Maybe b -> m b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m b
g b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
apply :: [IO (Maybe a)] -> IO (Maybe a)
apply :: forall a. [IO (Maybe a)] -> IO (Maybe a)
apply [] = Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
apply (IO (Maybe a)
x:[IO (Maybe a)]
xs) = do x' <- IO (Maybe a)
x
if isJust x'
then return x'
else apply xs
platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
#if defined(CAN_LOAD_DLL)
arch :: Arch
arch = Platform -> Arch
platformArch Platform
platform
#endif
os :: OS
os = Platform -> OS
platformOS Platform
platform
searchForLibUsingGcc :: Logger -> DynFlags -> String -> [FilePath] -> IO (Maybe FilePath)
searchForLibUsingGcc :: Logger -> DynFlags -> String -> [String] -> IO (Maybe String)
searchForLibUsingGcc Logger
logger DynFlags
dflags String
so [String]
dirs = do
str <- Logger -> DynFlags -> [Option] -> IO String
askLd Logger
logger DynFlags
dflags ((String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> Option
FileOption String
"-B") [String]
dirs
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [String -> Option
Option String
"--print-file-name", String -> Option
Option String
so])
let file = case String -> [String]
lines String
str of
[] -> String
""
String
l:[String]
_ -> String
l
if (file == so)
then return Nothing
else do b <- doesFileExist file
return (if b then Just file else Nothing)
getGCCPaths :: Logger -> DynFlags -> OS -> IO [FilePath]
getGCCPaths :: Logger -> DynFlags -> OS -> IO [String]
getGCCPaths Logger
logger DynFlags
dflags OS
os
| OS
os OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32 Bool -> Bool -> Bool
|| Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
ArchWasm32 =
do gcc_dirs <- Logger -> DynFlags -> String -> IO [String]
getGccSearchDirectory Logger
logger DynFlags
dflags String
"libraries"
sys_dirs <- getSystemDirectories
return $ nub $ gcc_dirs ++ sys_dirs
| Bool
otherwise = [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
{-# NOINLINE gccSearchDirCache #-}
gccSearchDirCache :: IORef [(String, [String])]
gccSearchDirCache :: IORef [(String, [String])]
gccSearchDirCache = IO (IORef [(String, [String])]) -> IORef [(String, [String])]
forall a. IO a -> a
unsafePerformIO (IO (IORef [(String, [String])]) -> IORef [(String, [String])])
-> IO (IORef [(String, [String])]) -> IORef [(String, [String])]
forall a b. (a -> b) -> a -> b
$ [(String, [String])] -> IO (IORef [(String, [String])])
forall a. a -> IO (IORef a)
newIORef []
getGccSearchDirectory :: Logger -> DynFlags -> String -> IO [FilePath]
getGccSearchDirectory :: Logger -> DynFlags -> String -> IO [String]
getGccSearchDirectory Logger
logger DynFlags
dflags String
key = do
cache <- IORef [(String, [String])] -> IO [(String, [String])]
forall a. IORef a -> IO a
readIORef IORef [(String, [String])]
gccSearchDirCache
case lookup key cache of
Just [String]
x -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
x
Maybe [String]
Nothing -> do
str <- Logger -> DynFlags -> [Option] -> IO String
askLd Logger
logger DynFlags
dflags [String -> Option
Option String
"--print-search-dirs"]
let line = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
str
name = String
key String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": ="
if null line
then return []
else do let val = String -> [String]
split (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String -> String -> String
find String
name String
line
dirs <- filterM doesDirectoryExist val
modifyIORef' gccSearchDirCache ((key, dirs):)
return val
where split :: FilePath -> [FilePath]
split :: String -> [String]
split String
r = case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
';', Char
':']) String
r of
(String
s, [] ) -> [String
s]
(String
s, (Char
_:String
xs)) -> String
s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String -> [String]
split String
xs
find :: String -> String -> String
find :: String -> String -> String
find String
r String
x = let lst :: [String]
lst = String -> [String]
lines String
x
val :: [String]
val = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String
r String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf`) [String]
lst
in case [String]
val of
[] -> []
String
x:[String]
_ -> case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'=') String
x of
(String
_ , []) -> []
(String
_, (Char
_:String
xs)) -> String
xs
getSystemDirectories :: IO [FilePath]
#if defined(mingw32_HOST_OS)
getSystemDirectories = fmap (:[]) getSystemDirectory
#else
getSystemDirectories :: IO [String]
getSystemDirectories = [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
#endif
addEnvPaths :: String -> [String] -> IO [String]
addEnvPaths :: String -> [String] -> IO [String]
addEnvPaths String
name [String]
list
= do
working_dir <- IO String
getCurrentDirectory
values <- lookupEnv name
case values of
Maybe String
Nothing -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
list
Just String
arr -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ [String]
list [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> String -> [String]
splitEnv String
working_dir String
arr
where
splitEnv :: FilePath -> String -> [String]
splitEnv :: String -> String -> [String]
splitEnv String
working_dir String
value =
case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
envListSep) String
value of
(String
x, [] ) ->
[if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
x then String
working_dir else String
x]
(String
x, (Char
_:String
xs)) ->
(if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
x then String
working_dir else String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String -> String -> [String]
splitEnv String
working_dir String
xs
#if defined(mingw32_HOST_OS)
envListSep = ';'
#else
envListSep :: Char
envListSep = Char
':'
#endif
maybePutSDoc :: Logger -> SDoc -> IO ()
maybePutSDoc :: Logger -> SDoc -> IO ()
maybePutSDoc Logger
logger SDoc
s
= Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Logger -> Int -> Bool
logVerbAtLeast Logger
logger Int
2) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg Logger
logger
MessageClass
MCInteractive
SrcSpan
noSrcSpan
(SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle SDoc
s
maybePutStr :: Logger -> String -> IO ()
maybePutStr :: Logger -> String -> IO ()
maybePutStr Logger
logger String
s = Logger -> SDoc -> IO ()
maybePutSDoc Logger
logger (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
s)
maybePutStrLn :: Logger -> String -> IO ()
maybePutStrLn :: Logger -> String -> IO ()
maybePutStrLn Logger
logger String
s = Logger -> SDoc -> IO ()
maybePutSDoc Logger
logger (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
s SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"\n")