{-# LANGUAGE CPP #-}
{-# LANGUAGE TupleSections, RecordWildCards #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
module GHC.Linker.Loader
   ( Loader (..)
   , LoaderState (..)
   , initLoaderState
   , uninitializedLoader
   , showLoaderState
   , getLoaderState
   
   , loadExpr
   , loadDecls
   , loadPackages
   , loadModule
   , loadCmdLineLibs
   , loadName
   , unload
   
   , withExtendedLoadedEnv
   , extendLoadedEnv
   , deleteFromLoadedEnv
   )
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
import GHC.Driver.Config.Diagnostic
import GHC.Driver.Config.Finder
import GHC.Tc.Utils.Monad
import GHC.Runtime.Interpreter
import GHCi.RemoteTypes
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.Panic.Plain
import GHC.Utils.Error
import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Unit.Env
import GHC.Unit.Finder
import GHC.Unit.Module
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.Deps
import GHC.Unit.Home.ModInfo
import GHC.Unit.State as Packages
import qualified GHC.Data.ShortText as ST
import qualified GHC.Data.Maybe as Maybes
import GHC.Data.FastString
import GHC.Linker.MacOS
import GHC.Linker.Dynamic
import GHC.Linker.Types
import Control.Monad
import qualified Data.Set as Set
import qualified Data.Map as M
import Data.Char (isSpace)
import Data.IORef
import Data.List (intercalate, isPrefixOf, isSuffixOf, nub, partition)
import Data.Maybe
import Control.Concurrent.MVar
import qualified Control.Monad.Catch as MC
import System.FilePath
import System.Directory
import System.IO.Unsafe
import System.Environment (lookupEnv)
#if defined(mingw32_HOST_OS)
import System.Win32.Info (getSystemDirectory)
#endif
import GHC.Utils.Exception
import GHC.Unit.Module.Graph
import GHC.Types.SourceFile
import GHC.Utils.Misc
import GHC.Iface.Load
import GHC.Unit.Home
import Data.Either
import Control.Applicative
uninitialised :: a
uninitialised :: forall a. a
uninitialised = String -> a
forall a. 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]
-> 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
    (LoaderState
pls, [Linkable]
links, PkgsLoaded
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 key elt. UniqDFM key elt
emptyUDFM)
       else do
         (LoaderState
pls', SuccessFlag
ok, [Linkable]
links, PkgsLoaded
pkgs) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls0 SrcSpan
noSrcSpan
                                      [(() :: Constraint) => Name -> Module
Name -> Module
nameModule Name
name]
         if SuccessFlag -> Bool
failed SuccessFlag
ok
           then GhcException -> IO (LoaderState, [Linkable], PkgsLoaded)
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"")
           else (LoaderState, [Linkable], PkgsLoaded)
-> IO (LoaderState, [Linkable], PkgsLoaded)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls', [Linkable]
links, PkgsLoaded
pkgs)
    case ClosureEnv -> Name -> Maybe (Name, ForeignHValue)
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv (LinkerEnv -> ClosureEnv
closure_env (LoaderState -> LinkerEnv
linker_env LoaderState
pls)) Name
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"
                        Maybe HValueRef
m <- Interp -> String -> IO (Maybe HValueRef)
lookupClosure Interp
interp (FastString -> String
unpackFS FastString
sym_to_find)
                        ForeignHValue
r <- case Maybe HValueRef
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)
                        (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
r, [Linkable]
links, PkgsLoaded
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 dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
   
   
   
   
   Maybe String
maybe_normal_osuf <- DynFlags -> Interp -> SrcSpan -> IO (Maybe String)
checkNonStdWay DynFlags
dflags Interp
interp SrcSpan
span
   
   ([Linkable]
lnks, [Linkable]
all_lnks, [UnitId]
pkgs, UniqDSet UnitId
this_pkgs_needed)
      <- HscEnv
-> LoaderState
-> Maybe String
-> SrcSpan
-> [Module]
-> IO ([Linkable], [Linkable], [UnitId], UniqDSet UnitId)
getLinkDeps HscEnv
hsc_env LoaderState
pls
           Maybe String
maybe_normal_osuf SrcSpan
span [Module]
needed_mods
   
   LoaderState
pls1 <- Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
loadPackages' Interp
interp HscEnv
hsc_env [UnitId]
pkgs LoaderState
pls
   (LoaderState
pls2, SuccessFlag
succ) <- Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadModuleLinkables Interp
interp HscEnv
hsc_env LoaderState
pls1 [Linkable]
lnks
   let this_pkgs_loaded :: PkgsLoaded
this_pkgs_loaded = PkgsLoaded -> UniqDFM UnitId UnitId -> PkgsLoaded
forall key 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 :: PkgsLoaded
all_pkgs_loaded = LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls2
       trans_pkgs_needed :: UniqDSet UnitId
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]
                                                                  ])
   (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls2, SuccessFlag
succ, [Linkable]
all_lnks, PkgsLoaded
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.
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
  Maybe LoaderState
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 :: [SDoc]
docs = case Maybe LoaderState
ls of
        Maybe LoaderState
Nothing  -> [ String -> SDoc
text String
"Loader not initialised"]
        Just LoaderState
pls -> [ String -> SDoc
text String
"Pkgs:" SDoc -> SDoc -> SDoc
<+> [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 key 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
text String
"Objs:" SDoc -> SDoc -> SDoc
<+> [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
text String
"BCOs:" SDoc -> SDoc -> SDoc
<+> [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)
                    ]
  SDoc -> IO SDoc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SDoc -> IO SDoc) -> SDoc -> IO SDoc
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle
         (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat (String -> SDoc
text String
"----- Loader state -----"SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
:[SDoc]
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
  
  Interp -> IO ()
initObjLinker Interp
interp
  
  LoaderState
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 ((() :: Constraint) => 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)
  
  Interp -> HscEnv -> LoaderState -> IO LoaderState
loadCmdLineLibs' Interp
interp HscEnv
hsc_env LoaderState
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' = (() :: Constraint) => UnitId -> HscEnv -> HscEnv
UnitId -> HscEnv -> HscEnv
hscSetActiveUnitId UnitId
uid HscEnv
hsc_env
      
      (Set UnitId
done', LoaderState
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 ((() :: Constraint) => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units HscEnv
hsc'))
      LoaderState
pls'' <- Interp -> HscEnv -> LoaderState -> IO LoaderState
loadCmdLineLibs'' Interp
interp HscEnv
hsc' LoaderState
pls'
      (Set UnitId, LoaderState) -> IO (Set UnitId, LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Set UnitId, LoaderState) -> IO (Set UnitId, LoaderState))
-> (Set UnitId, LoaderState) -> IO (Set UnitId, LoaderState)
forall a b. (a -> b) -> a -> b
$ (UnitId -> Set UnitId -> Set UnitId
forall a. Ord a => a -> Set a -> Set a
Set.insert UnitId
uid Set UnitId
done', LoaderState
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
      
      [String]
gcc_paths <- Logger -> DynFlags -> OS -> IO [String]
getGCCPaths Logger
logger DynFlags
dflags OS
os
      [String]
lib_paths_env <- String -> [String] -> IO [String]
addEnvPaths String
"LIBRARY_PATH" [String]
lib_paths_base
      Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"Search directories (user):"
      Logger -> String -> IO ()
maybePutStr Logger
logger ([String] -> String
unlines ([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 -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
lib_paths_env)
      Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"Search directories (gcc):"
      Logger -> String -> IO ()
maybePutStr Logger
logger ([String] -> String
unlines ([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 -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
gcc_paths)
      [LibrarySpec]
libspecs
        <- (String -> IO LibrarySpec) -> [String] -> IO [LibrarySpec]
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 (Interp
-> HscEnv
-> Bool
-> [String]
-> [String]
-> String
-> IO LibrarySpec
locateLib Interp
interp HscEnv
hsc_env Bool
False [String]
lib_paths_env [String]
gcc_paths) [String]
minus_ls
      
      [Maybe LibrarySpec]
classified_ld_inputs <- (String -> IO (Maybe LibrarySpec))
-> [String] -> IO [Maybe LibrarySpec]
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 (Logger -> Platform -> String -> IO (Maybe LibrarySpec)
classifyLdInput Logger
logger Platform
platform)
                                [ String
f | FileOption String
_ String
f <- [Option]
cmdline_ld_inputs ]
      
      let platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
      let ([String]
framework_paths, [String]
frameworks) =
            if Platform -> Bool
platformUsesFrameworks Platform
platform
             then (DynFlags -> [String]
frameworkPaths DynFlags
dflags, DynFlags -> [String]
cmdlineFrameworks DynFlags
dflags)
              else ([],[])
      
      let cmdline_lib_specs :: [LibrarySpec]
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 [LibrarySpec] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [LibrarySpec]
cmdline_lib_specs
         then LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls
         else do
           
           
           let all_paths :: [String]
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]
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
           [String]
all_paths_env <- String -> [String] -> IO [String]
addEnvPaths String
"LD_LIBRARY_PATH" [String]
all_paths
           [Ptr ()]
pathCache <- (String -> IO (Ptr ())) -> [String] -> IO [Ptr ()]
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 (Interp -> String -> IO (Ptr ())
addLibrarySearchPath Interp
interp) [String]
all_paths_env
           let merged_specs :: [LibrarySpec]
merged_specs = [LibrarySpec] -> [LibrarySpec]
mergeStaticObjects [LibrarySpec]
cmdline_lib_specs
           LoaderState
pls1 <- (LoaderState -> LibrarySpec -> IO LoaderState)
-> LoaderState -> [LibrarySpec] -> IO LoaderState
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (Interp
-> HscEnv
-> [String]
-> [String]
-> LoaderState
-> LibrarySpec
-> IO LoaderState
preloadLib Interp
interp HscEnv
hsc_env [String]
lib_paths [String]
framework_paths) LoaderState
pls
                         [LibrarySpec]
merged_specs
           Logger -> String -> IO ()
maybePutStr Logger
logger String
"final link ... "
           SuccessFlag
ok <- Interp -> IO SuccessFlag
resolveObjs Interp
interp
           
           (Ptr () -> IO Bool) -> [Ptr ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> Ptr () -> IO Bool
removeLibrarySearchPath Interp
interp) ([Ptr ()] -> IO ()) -> [Ptr ()] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Ptr ()] -> [Ptr ()]
forall a. [a] -> [a]
reverse [Ptr ()]
pathCache
           if SuccessFlag -> Bool
succeeded SuccessFlag
ok then Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
           else GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"linking extra libraries/objects failed")
           LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
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
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
      (Bool
b, LoaderState
pls1) <- [String] -> [String] -> IO (Bool, LoaderState)
preload_statics [String]
lib_paths [String]
static_ishs
      Logger -> String -> IO ()
maybePutStrLn Logger
logger (if Bool
b  then String
"done" else String
"not found")
      LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls1
    Archive String
static_ish -> do
      Bool
b <- [String] -> String -> IO Bool
preload_static_archive [String]
lib_paths String
static_ish
      Logger -> String -> IO ()
maybePutStrLn Logger
logger (if Bool
b  then String
"done" else String
"not found")
      LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls
    DLL String
dll_unadorned -> do
      Maybe String
maybe_errstr <- Interp -> String -> IO (Maybe String)
loadDLL Interp
interp (Platform -> String -> String
platformSOName Platform
platform String
dll_unadorned)
      case Maybe String
maybe_errstr of
         Maybe String
Nothing -> Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
         Just 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
         Just 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"
           Maybe String
err2 <- Interp -> String -> IO (Maybe String)
loadDLL Interp
interp String
libfile
           case Maybe String
err2 of
             Maybe String
Nothing -> Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done"
             Just String
_  -> String -> [String] -> LibrarySpec -> IO ()
preloadFailed String
mm [String]
lib_paths LibrarySpec
lib_spec
      LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls
    DLLPath String
dll_path -> do
      do Maybe String
maybe_errstr <- Interp -> String -> IO (Maybe String)
loadDLL Interp
interp String
dll_path
         case Maybe String
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]
lib_paths LibrarySpec
lib_spec
         LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
pls
    Framework String
framework ->
      if Platform -> Bool
platformUsesFrameworks (DynFlags -> Platform
targetPlatform DynFlags
dflags)
      then do Maybe String
maybe_errstr <- Interp -> [String] -> String -> IO (Maybe String)
loadFramework Interp
interp [String]
framework_paths String
framework
              case Maybe String
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
              LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
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 Bool
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 Bool -> Bool
not Bool
b then (Bool, LoaderState) -> IO (Bool, LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, LoaderState
pls)
                     else if Bool
hostIsDynamic
                             then  do LoaderState
pls1 <- Interp -> HscEnv -> LoaderState -> [String] -> IO LoaderState
dynLoadObjs Interp
interp HscEnv
hsc_env LoaderState
pls [String]
names
                                      (Bool, LoaderState) -> IO (Bool, LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, LoaderState
pls1)
                             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]
names
                                      (Bool, LoaderState) -> IO (Bool, LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, LoaderState
pls)
    preload_static_archive :: [String] -> String -> IO Bool
preload_static_archive [String]
_paths String
name
       = do Bool
b <- String -> IO Bool
doesFileExist String
name
            if Bool -> Bool
not Bool
b then Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
                     else do if Bool
hostIsDynamic
                                 then GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO ()) -> GhcException -> IO ()
forall a b. (a -> b) -> a -> b
$
                                      String -> GhcException
CmdLineError String
dynamic_msg
                                 else Interp -> String -> IO ()
loadArchive Interp
interp String
name
                             Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
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
    
    (LoaderState
pls, SuccessFlag
ok, [Linkable]
_, PkgsLoaded
_) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls0 SrcSpan
span [Module]
needed_mods
    if SuccessFlag -> Bool
failed SuccessFlag
ok
      then GhcException -> IO (LoaderState, ForeignHValue)
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"")
      else do
        
        
        let le :: LinkerEnv
le = LoaderState -> LinkerEnv
linker_env LoaderState
pls
            nobreakarray :: a
nobreakarray = String -> a
forall a. HasCallStack => String -> a
error String
"no break array"
            bco_ix :: NameEnv Int
bco_ix = [(Name, Int)] -> NameEnv Int
forall a. [(Name, a)] -> NameEnv a
mkNameEnv [(UnlinkedBCO -> Name
unlinkedBCOName UnlinkedBCO
root_ul_bco, Int
0)]
        ResolvedBCO
resolved <- Interp
-> LinkerEnv
-> NameEnv Int
-> RemoteRef BreakArray
-> UnlinkedBCO
-> IO ResolvedBCO
linkBCO Interp
interp LinkerEnv
le NameEnv Int
bco_ix RemoteRef BreakArray
forall a. a
nobreakarray UnlinkedBCO
root_ul_bco
        BCOOpts
bco_opts <- DynFlags -> IO BCOOpts
initBCOOpts (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
        [HValueRef
root_hvref] <- Interp -> BCOOpts -> [ResolvedBCO] -> IO [HValueRef]
createBCOs Interp
interp BCOOpts
bco_opts [ResolvedBCO
resolved]
        ForeignHValue
fhv <- Interp -> HValueRef -> IO ForeignHValue
forall a. Interp -> RemoteRef a -> IO (ForeignRef a)
mkFinalizedHValue Interp
interp HValueRef
root_hvref
        (LoaderState, ForeignHValue) -> IO (LoaderState, ForeignHValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls, ForeignHValue
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 = [ (() :: Constraint) => 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)  
                   ]                        
        
        
        
        
dieWith :: DynFlags -> SrcSpan -> SDoc -> IO a
dieWith :: forall a. DynFlags -> SrcSpan -> SDoc -> IO a
dieWith DynFlags
dflags SrcSpan
span SDoc
msg = GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (MessageClass -> SrcSpan -> SDoc -> SDoc
mkLocMessage MessageClass
MCFatal SrcSpan
span SDoc
msg)))
checkNonStdWay :: DynFlags -> Interp -> SrcSpan -> IO (Maybe FilePath)
checkNonStdWay :: DynFlags -> Interp -> SrcSpan -> IO (Maybe String)
checkNonStdWay DynFlags
_dflags Interp
interp SrcSpan
_srcspan
  | ExternalInterp {} <- Interp -> InterpInstance
interpInstance Interp
interp = Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
    
    
    
#if defined(HAVE_INTERNAL_INTERPRETER)
checkNonStdWay DynFlags
dflags Interp
_interp SrcSpan
srcspan
  | Ways
hostFullWays Ways -> Ways -> Bool
forall a. Eq a => a -> a -> Bool
== Ways
targetFullWays = Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
    
    
  | DynFlags -> String
objectSuf_ DynFlags
dflags String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
normalObjectSuffix Bool -> Bool -> Bool
&& Bool -> Bool
not (Ways -> Bool
forall a. Set a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Ways
targetFullWays)
  = DynFlags -> SrcSpan -> IO (Maybe String)
failNonStd DynFlags
dflags SrcSpan
srcspan
  | Bool
otherwise = Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just (String
hostWayTag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"o"))
  where
    targetFullWays :: Ways
targetFullWays = Ways -> Ways
fullWays (DynFlags -> Ways
ways DynFlags
dflags)
    hostWayTag :: String
hostWayTag = case Ways -> String
waysTag Ways
hostFullWays of
                  String
"" -> String
""
                  String
tag -> String
tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_"
    normalObjectSuffix :: String
    normalObjectSuffix :: String
normalObjectSuffix = Phase -> String
phaseInputExt Phase
StopLn
data Way' = Normal | Prof | Dyn
failNonStd :: DynFlags -> SrcSpan -> IO (Maybe FilePath)
failNonStd :: DynFlags -> SrcSpan -> IO (Maybe String)
failNonStd DynFlags
dflags SrcSpan
srcspan = DynFlags -> SrcSpan -> SDoc -> IO (Maybe String)
forall a. DynFlags -> SrcSpan -> SDoc -> IO a
dieWith DynFlags
dflags SrcSpan
srcspan (SDoc -> IO (Maybe String)) -> SDoc -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$
  String -> SDoc
text String
"Cannot load" SDoc -> SDoc -> SDoc
<+> Way' -> SDoc
pprWay' Way'
compWay SDoc -> SDoc -> SDoc
<+>
     String -> SDoc
text String
"objects when GHC is built" SDoc -> SDoc -> SDoc
<+> Way' -> SDoc
pprWay' Way'
ghciWay SDoc -> SDoc -> SDoc
$$
  String -> SDoc
text String
"To fix this, either:" SDoc -> SDoc -> SDoc
$$
  String -> SDoc
text String
"  (1) Use -fexternal-interpreter, or" SDoc -> SDoc -> SDoc
$$
  SDoc
buildTwiceMsg
    where compWay :: Way'
compWay
            | DynFlags -> Ways
ways DynFlags
dflags Ways -> Way -> Bool
`hasWay` Way
WayDyn  = Way'
Dyn
            | DynFlags -> Ways
ways DynFlags
dflags Ways -> Way -> Bool
`hasWay` Way
WayProf = Way'
Prof
            | Bool
otherwise = Way'
Normal
          ghciWay :: Way'
ghciWay
            | Bool
hostIsDynamic = Way'
Dyn
            | Bool
hostIsProfiled = Way'
Prof
            | Bool
otherwise = Way'
Normal
          buildTwiceMsg :: SDoc
buildTwiceMsg = case (Way'
ghciWay, Way'
compWay) of
            (Way'
Normal, Way'
Dyn) -> SDoc
dynamicTooMsg
            (Way'
Dyn, Way'
Normal) -> SDoc
dynamicTooMsg
            (Way', Way')
_ ->
              String -> SDoc
text String
"  (2) Build the program twice: once" SDoc -> SDoc -> SDoc
<+>
                Way' -> SDoc
pprWay' Way'
ghciWay SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", and then" SDoc -> SDoc -> SDoc
$$
              String -> SDoc
text String
"      " SDoc -> SDoc -> SDoc
<> Way' -> SDoc
pprWay' Way'
compWay SDoc -> SDoc -> SDoc
<+>
                String -> SDoc
text String
"using -osuf to set a different object file suffix."
          dynamicTooMsg :: SDoc
dynamicTooMsg = String -> SDoc
text String
"  (2) Use -dynamic-too," SDoc -> SDoc -> SDoc
<+>
            String -> SDoc
text String
"and use -osuf and -dynosuf to set object file suffixes as needed."
          pprWay' :: Way' -> SDoc
          pprWay' :: Way' -> SDoc
pprWay' Way'
way = String -> SDoc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ case Way'
way of
            Way'
Normal -> String
"the normal way"
            Way'
Prof -> String
"with -prof"
            Way'
Dyn -> String
"with -dynamic"
#endif
getLinkDeps :: HscEnv
            -> LoaderState
            -> Maybe FilePath                   
            -> SrcSpan                          
            -> [Module]                         
            -> IO ([Linkable], [Linkable], [UnitId], UniqDSet UnitId)     
            
            
getLinkDeps :: HscEnv
-> LoaderState
-> Maybe String
-> SrcSpan
-> [Module]
-> IO ([Linkable], [Linkable], [UnitId], UniqDSet UnitId)
getLinkDeps HscEnv
hsc_env LoaderState
pls Maybe String
replace_osuf SrcSpan
span [Module]
mods
 = do {
        
        
      ; ([Module]
mods_s, UniqDSet UnitId
pkgs_s) <-
          
          
          
          if GhcMode -> Bool
isOneShot (DynFlags -> GhcMode
ghcMode DynFlags
dflags)
            then [Module]
-> UniqDSet Module
-> UniqDSet UnitId
-> IO ([Module], UniqDSet UnitId)
follow_deps ((Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filterOut Module -> Bool
isInteractiveModule [Module]
mods)
                              UniqDSet Module
forall a. UniqDSet a
emptyUniqDSet UniqDSet UnitId
forall a. UniqDSet a
emptyUniqDSet;
            else do
              ([UniqDSet UnitId]
pkgs, [Maybe Module]
mmods) <- [(UniqDSet UnitId, Maybe Module)]
-> ([UniqDSet UnitId], [Maybe Module])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(UniqDSet UnitId, Maybe Module)]
 -> ([UniqDSet UnitId], [Maybe Module]))
-> IO [(UniqDSet UnitId, Maybe Module)]
-> IO ([UniqDSet UnitId], [Maybe Module])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ModNodeKeyWithUid -> IO (UniqDSet UnitId, Maybe Module))
-> [ModNodeKeyWithUid] -> IO [(UniqDSet UnitId, Maybe Module)]
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 ModNodeKeyWithUid -> IO (UniqDSet UnitId, Maybe Module)
get_mod_info [ModNodeKeyWithUid]
all_home_mods
              ([Module], UniqDSet UnitId) -> IO ([Module], UniqDSet UnitId)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Maybe Module] -> [Module]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Module]
mmods, [UniqDSet UnitId] -> UniqDSet UnitId
forall a. [UniqDSet a] -> UniqDSet a
unionManyUniqDSets (UniqDSet UnitId
init_pkg_set UniqDSet UnitId -> [UniqDSet UnitId] -> [UniqDSet UnitId]
forall a. a -> [a] -> [a]
: [UniqDSet UnitId]
pkgs))
      ; let
        
        
            ([Module]
mods_needed, [Linkable]
links_got) = [Either Module Linkable] -> ([Module], [Linkable])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ((Module -> Either Module Linkable)
-> [Module] -> [Either Module Linkable]
forall a b. (a -> b) -> [a] -> [b]
map Module -> Either Module Linkable
split_mods [Module]
mods_s)
            pkgs_needed :: [UnitId]
pkgs_needed = UniqDFM UnitId UnitId -> [UnitId]
forall key elt. UniqDFM key elt -> [elt]
eltsUDFM (UniqDFM UnitId UnitId -> [UnitId])
-> UniqDFM UnitId UnitId -> [UnitId]
forall a b. (a -> b) -> a -> b
$ UniqDSet UnitId -> UniqDFM UnitId UnitId
forall a. UniqDSet a -> UniqDFM a a
getUniqDSet UniqDSet UnitId
pkgs_s UniqDFM UnitId UnitId -> PkgsLoaded -> UniqDFM UnitId UnitId
forall key elt elt2.
UniqDFM key elt -> UniqDFM key elt2 -> UniqDFM key elt
`minusUDFM` LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls
            split_mods :: Module -> Either Module Linkable
split_mods Module
mod =
                let is_linked :: Maybe Linkable
is_linked = LinkableSet -> Module -> Maybe Linkable
findModuleLinkable_maybe (LoaderState -> LinkableSet
objs_loaded LoaderState
pls) Module
mod Maybe Linkable -> Maybe Linkable -> Maybe Linkable
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LinkableSet -> Module -> Maybe Linkable
findModuleLinkable_maybe (LoaderState -> LinkableSet
bcos_loaded LoaderState
pls) Module
mod
                in case Maybe Linkable
is_linked of
                     Just Linkable
linkable -> Linkable -> Either Module Linkable
forall a b. b -> Either a b
Right Linkable
linkable
                     Maybe Linkable
Nothing -> Module -> Either Module Linkable
forall a b. a -> Either a b
Left Module
mod
        
        
        
      ; let { osuf :: String
osuf = DynFlags -> String
objectSuf DynFlags
dflags }
      ; [Linkable]
lnks_needed <- (Module -> IO Linkable) -> [Module] -> IO [Linkable]
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 -> Module -> IO Linkable
get_linkable String
osuf) [Module]
mods_needed
      ; ([Linkable], [Linkable], [UnitId], UniqDSet UnitId)
-> IO ([Linkable], [Linkable], [UnitId], UniqDSet UnitId)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Linkable]
lnks_needed, [Linkable]
links_got [Linkable] -> [Linkable] -> [Linkable]
forall a. [a] -> [a] -> [a]
++ [Linkable]
lnks_needed, [UnitId]
pkgs_needed, UniqDSet UnitId
pkgs_s) }
  where
    dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
    mod_graph :: ModuleGraph
mod_graph = HscEnv -> ModuleGraph
hsc_mod_graph HscEnv
hsc_env
    
    
    
    
    
    
    
    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
    make_deps_loop :: (UniqDSet UnitId, Set NodeKey)
-> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey)
make_deps_loop (UniqDSet UnitId, Set NodeKey)
found [] = (UniqDSet UnitId, Set NodeKey)
found
    make_deps_loop found :: (UniqDSet UnitId, Set NodeKey)
found@(UniqDSet UnitId
found_units, Set NodeKey
found_mods) (ModNodeKeyWithUid
nk:[ModNodeKeyWithUid]
nexts)
      | ModNodeKeyWithUid -> NodeKey
NodeKey_Module ModNodeKeyWithUid
nk NodeKey -> Set NodeKey -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set NodeKey
found_mods = (UniqDSet UnitId, Set NodeKey)
-> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey)
make_deps_loop (UniqDSet UnitId, Set NodeKey)
found [ModNodeKeyWithUid]
nexts
      | Bool
otherwise =
        case NodeKey -> Map NodeKey (Set NodeKey) -> Maybe (Set NodeKey)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ModNodeKeyWithUid -> NodeKey
NodeKey_Module ModNodeKeyWithUid
nk) (ModuleGraph -> Map NodeKey (Set NodeKey)
mgTransDeps ModuleGraph
mod_graph) of
            Just Set NodeKey
trans_deps ->
              let deps :: Set NodeKey
deps = NodeKey -> Set NodeKey -> Set NodeKey
forall a. Ord a => a -> Set a -> Set a
Set.insert (ModNodeKeyWithUid -> NodeKey
NodeKey_Module ModNodeKeyWithUid
nk) Set NodeKey
trans_deps
                  
                  
                  todo_boot_mods :: [ModNodeKeyWithUid]
todo_boot_mods = [ModuleNameWithIsBoot -> UnitId -> ModNodeKeyWithUid
ModNodeKeyWithUid (ModuleName -> IsBootInterface -> ModuleNameWithIsBoot
forall mod. mod -> IsBootInterface -> GenWithIsBoot mod
GWIB ModuleName
mn IsBootInterface
NotBoot) UnitId
uid | NodeKey_Module (ModNodeKeyWithUid (GWIB ModuleName
mn IsBootInterface
IsBoot) UnitId
uid) <- Set NodeKey -> [NodeKey]
forall a. Set a -> [a]
Set.toList Set NodeKey
trans_deps]
              in (UniqDSet UnitId, Set NodeKey)
-> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey)
make_deps_loop (UniqDSet UnitId
found_units, Set NodeKey
deps Set NodeKey -> Set NodeKey -> Set NodeKey
forall a. Ord a => Set a -> Set a -> Set a
`Set.union` Set NodeKey
found_mods) ([ModNodeKeyWithUid]
todo_boot_mods [ModNodeKeyWithUid] -> [ModNodeKeyWithUid] -> [ModNodeKeyWithUid]
forall a. [a] -> [a] -> [a]
++ [ModNodeKeyWithUid]
nexts)
            Maybe (Set NodeKey)
Nothing ->
              let (ModNodeKeyWithUid ModuleNameWithIsBoot
_ UnitId
uid) = ModNodeKeyWithUid
nk
              in (UniqDSet UnitId, Set NodeKey)
-> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey)
make_deps_loop (UniqDSet UnitId -> UnitId -> UniqDSet UnitId
forall a. Uniquable a => UniqDSet a -> a -> UniqDSet a
addOneToUniqDSet UniqDSet UnitId
found_units UnitId
uid, Set NodeKey
found_mods) [ModNodeKeyWithUid]
nexts
    mkNk :: Module -> ModNodeKeyWithUid
mkNk Module
m = ModuleNameWithIsBoot -> UnitId -> ModNodeKeyWithUid
ModNodeKeyWithUid (ModuleName -> IsBootInterface -> ModuleNameWithIsBoot
forall mod. mod -> IsBootInterface -> GenWithIsBoot mod
GWIB (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m) IsBootInterface
NotBoot) (Module -> UnitId
moduleUnitId Module
m)
    (UniqDSet UnitId
init_pkg_set, Set NodeKey
all_deps) = (UniqDSet UnitId, Set NodeKey)
-> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey)
make_deps_loop (UniqDSet UnitId
forall a. UniqDSet a
emptyUniqDSet, Set NodeKey
forall a. Set a
Set.empty) ([ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey))
-> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set NodeKey)
forall a b. (a -> b) -> a -> b
$ (Module -> ModNodeKeyWithUid) -> [Module] -> [ModNodeKeyWithUid]
forall a b. (a -> b) -> [a] -> [b]
map Module -> ModNodeKeyWithUid
mkNk ((Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filterOut Module -> Bool
isInteractiveModule [Module]
mods)
    all_home_mods :: [ModNodeKeyWithUid]
all_home_mods = [ModNodeKeyWithUid
with_uid | NodeKey_Module ModNodeKeyWithUid
with_uid <- Set NodeKey -> [NodeKey]
forall a. Set a -> [a]
Set.toList Set NodeKey
all_deps]
    get_mod_info :: ModNodeKeyWithUid -> IO (UniqDSet UnitId, Maybe Module)
get_mod_info (ModNodeKeyWithUid ModuleNameWithIsBoot
gwib UnitId
uid) =
      case UnitEnvGraph HomeUnitEnv
-> UnitId -> ModuleName -> Maybe HomeModInfo
lookupHug (HscEnv -> UnitEnvGraph HomeUnitEnv
hsc_HUG HscEnv
hsc_env) UnitId
uid (ModuleNameWithIsBoot -> ModuleName
forall mod. GenWithIsBoot mod -> mod
gwib_mod ModuleNameWithIsBoot
gwib) of
        Just HomeModInfo
hmi ->
          let iface :: ModIface
iface = (HomeModInfo -> ModIface
hm_iface HomeModInfo
hmi)
              mmod :: IO (Maybe Module)
mmod = case ModIface -> HscSource
forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src ModIface
iface of
                      HscSource
HsBootFile -> Module -> IO (Maybe Module)
forall a. Module -> IO a
link_boot_mod_error (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface)
                      HscSource
_ -> Maybe Module -> IO (Maybe Module)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Module -> IO (Maybe Module))
-> Maybe Module -> IO (Maybe Module)
forall a b. (a -> b) -> a -> b
$ Module -> Maybe Module
forall a. a -> Maybe a
Just (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface)
          in ([UnitId] -> UniqDSet UnitId
forall a. Uniquable a => [a] -> UniqDSet a
mkUniqDSet ([UnitId] -> UniqDSet UnitId) -> [UnitId] -> UniqDSet UnitId
forall a b. (a -> b) -> a -> b
$ Set UnitId -> [UnitId]
forall a. Set a -> [a]
Set.toList (Set UnitId -> [UnitId]) -> Set UnitId -> [UnitId]
forall a b. (a -> b) -> a -> b
$ Dependencies -> Set UnitId
dep_direct_pkgs (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface),) (Maybe Module -> (UniqDSet UnitId, Maybe Module))
-> IO (Maybe Module) -> IO (UniqDSet UnitId, Maybe Module)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  IO (Maybe Module)
mmod
        Maybe HomeModInfo
Nothing ->
          let err :: SDoc
err = String -> SDoc
text String
"getLinkDeps: Home module not loaded" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModuleNameWithIsBoot -> ModuleName
forall mod. GenWithIsBoot mod -> mod
gwib_mod ModuleNameWithIsBoot
gwib) SDoc -> SDoc -> SDoc
<+> UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnitId
uid
          in GhcException -> IO (UniqDSet UnitId, Maybe Module)
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags SDoc
err))
       
       
       
       
       
       
       
    follow_deps :: [Module]             
                -> UniqDSet Module         
                -> UniqDSet UnitId          
                -> IO ([Module], UniqDSet UnitId) 
    follow_deps :: [Module]
-> UniqDSet Module
-> UniqDSet UnitId
-> IO ([Module], UniqDSet UnitId)
follow_deps []     UniqDSet Module
acc_mods UniqDSet UnitId
acc_pkgs
        = ([Module], UniqDSet UnitId) -> IO ([Module], UniqDSet UnitId)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (UniqDSet Module -> [Module]
forall a. UniqDSet a -> [a]
uniqDSetToList UniqDSet Module
acc_mods, UniqDSet UnitId
acc_pkgs)
    follow_deps (Module
mod:[Module]
mods) UniqDSet Module
acc_mods UniqDSet UnitId
acc_pkgs
        = do
          MaybeErr SDoc ModIface
mb_iface <- SDoc
-> HscEnv
-> IfG (MaybeErr SDoc ModIface)
-> IO (MaybeErr SDoc ModIface)
forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
text String
"getLinkDeps") HscEnv
hsc_env (IfG (MaybeErr SDoc ModIface) -> IO (MaybeErr SDoc ModIface))
-> IfG (MaybeErr SDoc ModIface) -> IO (MaybeErr SDoc ModIface)
forall a b. (a -> b) -> a -> b
$
                        SDoc -> Module -> WhereFrom -> IfG (MaybeErr SDoc ModIface)
forall lcl.
SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr SDoc ModIface)
loadInterface SDoc
msg Module
mod (IsBootInterface -> WhereFrom
ImportByUser IsBootInterface
NotBoot)
          ModIface
iface <- case MaybeErr SDoc ModIface
mb_iface of
                    Maybes.Failed SDoc
err      -> GhcException -> IO ModIface
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags SDoc
err))
                    Maybes.Succeeded ModIface
iface -> ModIface -> IO ModIface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface
          Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ModIface -> IsBootInterface
mi_boot ModIface
iface IsBootInterface -> IsBootInterface -> Bool
forall a. Eq a => a -> a -> Bool
== IsBootInterface
IsBoot) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Module -> IO ()
forall a. Module -> IO a
link_boot_mod_error Module
mod
          let
            pkg :: Unit
pkg = Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
mod
            deps :: Dependencies
deps  = ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface
            pkg_deps :: Set UnitId
pkg_deps = Dependencies -> Set UnitId
dep_direct_pkgs Dependencies
deps
            ([ModuleName]
boot_deps, [ModuleName]
mod_deps) = (((UnitId, ModuleNameWithIsBoot) -> Either ModuleName ModuleName)
 -> [(UnitId, ModuleNameWithIsBoot)]
 -> ([ModuleName], [ModuleName]))
-> [(UnitId, ModuleNameWithIsBoot)]
-> ((UnitId, ModuleNameWithIsBoot) -> Either ModuleName ModuleName)
-> ([ModuleName], [ModuleName])
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((UnitId, ModuleNameWithIsBoot) -> Either ModuleName ModuleName)
-> [(UnitId, ModuleNameWithIsBoot)] -> ([ModuleName], [ModuleName])
forall a b c. (a -> Either b c) -> [a] -> ([b], [c])
partitionWith (Set (UnitId, ModuleNameWithIsBoot)
-> [(UnitId, ModuleNameWithIsBoot)]
forall a. Set a -> [a]
Set.toList (Dependencies -> Set (UnitId, ModuleNameWithIsBoot)
dep_direct_mods Dependencies
deps)) (((UnitId, ModuleNameWithIsBoot) -> Either ModuleName ModuleName)
 -> ([ModuleName], [ModuleName]))
-> ((UnitId, ModuleNameWithIsBoot) -> Either ModuleName ModuleName)
-> ([ModuleName], [ModuleName])
forall a b. (a -> b) -> a -> b
$
              \case
                (UnitId
_, GWIB ModuleName
m IsBootInterface
IsBoot)  -> ModuleName -> Either ModuleName ModuleName
forall a b. a -> Either a b
Left ModuleName
m
                (UnitId
_, GWIB ModuleName
m IsBootInterface
NotBoot) -> ModuleName -> Either ModuleName ModuleName
forall a b. b -> Either a b
Right ModuleName
m
            mod_deps' :: [Module]
mod_deps' = case HscEnv -> Maybe HomeUnit
hsc_home_unit_maybe HscEnv
hsc_env of
                          Maybe HomeUnit
Nothing -> []
                          Just HomeUnit
home_unit -> (Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Module -> Bool) -> Module -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Module -> UniqDSet Module -> Bool
forall a. Uniquable a => a -> UniqDSet a -> Bool
`elementOfUniqDSet` UniqDSet Module
acc_mods)) ((ModuleName -> Module) -> [ModuleName] -> [Module]
forall a b. (a -> b) -> [a] -> [b]
map (HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit) ([ModuleName] -> [Module]) -> [ModuleName] -> [Module]
forall a b. (a -> b) -> a -> b
$ ([ModuleName]
boot_deps [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ [ModuleName]
mod_deps))
            acc_mods' :: UniqDSet Module
acc_mods'  = case HscEnv -> Maybe HomeUnit
hsc_home_unit_maybe HscEnv
hsc_env of
                          Maybe HomeUnit
Nothing -> UniqDSet Module
acc_mods
                          Just HomeUnit
home_unit -> UniqDSet Module -> [Module] -> UniqDSet Module
forall a. Uniquable a => UniqDSet a -> [a] -> UniqDSet a
addListToUniqDSet UniqDSet Module
acc_mods (Module
mod Module -> [Module] -> [Module]
forall a. a -> [a] -> [a]
: (ModuleName -> Module) -> [ModuleName] -> [Module]
forall a b. (a -> b) -> [a] -> [b]
map (HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit) [ModuleName]
mod_deps)
            acc_pkgs' :: UniqDSet UnitId
acc_pkgs'  = UniqDSet UnitId -> [UnitId] -> UniqDSet UnitId
forall a. Uniquable a => UniqDSet a -> [a] -> UniqDSet a
addListToUniqDSet UniqDSet UnitId
acc_pkgs (Set UnitId -> [UnitId]
forall a. Set a -> [a]
Set.toList Set UnitId
pkg_deps)
          case HscEnv -> Maybe HomeUnit
hsc_home_unit_maybe HscEnv
hsc_env of
            Just HomeUnit
home_unit | HomeUnit -> Unit -> Bool
isHomeUnit HomeUnit
home_unit Unit
pkg ->  [Module]
-> UniqDSet Module
-> UniqDSet UnitId
-> IO ([Module], UniqDSet UnitId)
follow_deps ([Module]
mod_deps' [Module] -> [Module] -> [Module]
forall a. [a] -> [a] -> [a]
++ [Module]
mods)
                                                                      UniqDSet Module
acc_mods' UniqDSet UnitId
acc_pkgs'
            Maybe HomeUnit
_ ->  [Module]
-> UniqDSet Module
-> UniqDSet UnitId
-> IO ([Module], UniqDSet UnitId)
follow_deps [Module]
mods UniqDSet Module
acc_mods (UniqDSet UnitId -> UnitId -> UniqDSet UnitId
forall a. Uniquable a => UniqDSet a -> a -> UniqDSet a
addOneToUniqDSet UniqDSet UnitId
acc_pkgs' (Unit -> UnitId
toUnitId Unit
pkg))
        where
           msg :: SDoc
msg = String -> SDoc
text String
"need to link module" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod SDoc -> SDoc -> SDoc
<+>
                  String -> SDoc
text String
"due to use of Template Haskell"
    link_boot_mod_error :: Module -> IO a
    link_boot_mod_error :: forall a. Module -> IO a
link_boot_mod_error Module
mod =
        GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (
            String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod SDoc -> SDoc -> SDoc
<+>
            String -> SDoc
text String
"cannot be linked; it is only available as a boot module")))
    no_obj :: Outputable a => a -> IO b
    no_obj :: forall a b. Outputable a => a -> IO b
no_obj a
mod = DynFlags -> SrcSpan -> SDoc -> IO b
forall a. DynFlags -> SrcSpan -> SDoc -> IO a
dieWith DynFlags
dflags SrcSpan
span (SDoc -> IO b) -> SDoc -> IO b
forall a b. (a -> b) -> a -> b
$
                     String -> SDoc
text String
"cannot find object file for module " SDoc -> SDoc -> SDoc
<>
                        SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
mod) SDoc -> SDoc -> SDoc
$$
                     SDoc
while_linking_expr
    while_linking_expr :: SDoc
while_linking_expr = String -> SDoc
text String
"while linking an interpreted expression"
        
    get_linkable :: String -> Module -> IO Linkable
get_linkable String
osuf Module
mod      
        | Just HomeModInfo
mod_info <- Module -> UnitEnvGraph HomeUnitEnv -> Maybe HomeModInfo
lookupHugByModule Module
mod (HscEnv -> UnitEnvGraph HomeUnitEnv
hsc_HUG HscEnv
hsc_env)
        = Linkable -> IO Linkable
adjust_linkable (String -> Maybe Linkable -> Linkable
forall a. HasCallStack => String -> Maybe a -> a
Maybes.expectJust String
"getLinkDeps" (HomeModInfo -> Maybe Linkable
hm_linkable HomeModInfo
mod_info))
        | Bool
otherwise
        = do    
                
             case HscEnv -> Maybe HomeUnit
hsc_home_unit_maybe HscEnv
hsc_env of
              Maybe HomeUnit
Nothing -> Module -> IO Linkable
forall a b. Outputable a => a -> IO b
no_obj Module
mod
              Just HomeUnit
home_unit -> do
                let fc :: FinderCache
fc = HscEnv -> FinderCache
hsc_FC HscEnv
hsc_env
                let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
                let fopts :: FinderOpts
fopts = DynFlags -> FinderOpts
initFinderOpts DynFlags
dflags
                FindResult
mb_stuff <- FinderCache
-> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult
findHomeModule FinderCache
fc FinderOpts
fopts HomeUnit
home_unit (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod)
                case FindResult
mb_stuff of
                  Found ModLocation
loc Module
mod -> ModLocation -> Module -> IO Linkable
found ModLocation
loc Module
mod
                  FindResult
_ -> ModuleName -> IO Linkable
forall a b. Outputable a => a -> IO b
no_obj (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod)
        where
            found :: ModLocation -> Module -> IO Linkable
found ModLocation
loc Module
mod = do {
                
               Maybe Linkable
mb_lnk <- Module -> ModLocation -> IO (Maybe Linkable)
findObjectLinkableMaybe Module
mod ModLocation
loc ;
               case Maybe Linkable
mb_lnk of {
                  Maybe Linkable
Nothing  -> Module -> IO Linkable
forall a b. Outputable a => a -> IO b
no_obj Module
mod ;
                  Just Linkable
lnk -> Linkable -> IO Linkable
adjust_linkable Linkable
lnk
              }}
            adjust_linkable :: Linkable -> IO Linkable
adjust_linkable Linkable
lnk
                | Just String
new_osuf <- Maybe String
replace_osuf = do
                        [Unlinked]
new_uls <- (Unlinked -> IO Unlinked) -> [Unlinked] -> IO [Unlinked]
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 -> Unlinked -> IO Unlinked
adjust_ul String
new_osuf)
                                        (Linkable -> [Unlinked]
linkableUnlinked Linkable
lnk)
                        Linkable -> IO Linkable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Linkable
lnk{ linkableUnlinked :: [Unlinked]
linkableUnlinked=[Unlinked]
new_uls }
                | Bool
otherwise =
                        Linkable -> IO Linkable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Linkable
lnk
            adjust_ul :: String -> Unlinked -> IO Unlinked
adjust_ul String
new_osuf (DotO String
file) = do
                Bool -> IO ()
forall (m :: * -> *). (HasCallStack, Applicative m) => Bool -> m ()
massert (String
osuf String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
file)
                let file_base :: String
file_base = Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> String -> Maybe String
stripExtension String
osuf String
file)
                    new_file :: String
new_file = String
file_base String -> String -> String
<.> String
new_osuf
                Bool
ok <- String -> IO Bool
doesFileExist String
new_file
                if (Bool -> Bool
not Bool
ok)
                   then DynFlags -> SrcSpan -> SDoc -> IO Unlinked
forall a. DynFlags -> SrcSpan -> SDoc -> IO a
dieWith DynFlags
dflags SrcSpan
span (SDoc -> IO Unlinked) -> SDoc -> IO Unlinked
forall a b. (a -> b) -> a -> b
$
                          String -> SDoc
text String
"cannot find object file "
                                SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (String -> SDoc
text String
new_file) SDoc -> SDoc -> SDoc
$$ SDoc
while_linking_expr
                   else Unlinked -> IO Unlinked
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Unlinked
DotO String
new_file)
            adjust_ul String
_ (DotA String
fp) = String -> IO Unlinked
forall a. String -> a
panic (String
"adjust_ul DotA " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
fp)
            adjust_ul String
_ (DotDLL String
fp) = String -> IO Unlinked
forall a. String -> a
panic (String
"adjust_ul DotDLL " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
fp)
            adjust_ul String
_ l :: Unlinked
l@(BCOs {}) = Unlinked -> IO Unlinked
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Unlinked
l
loadDecls :: Interp -> HscEnv -> SrcSpan -> CompiledByteCode -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
loadDecls :: Interp
-> HscEnv
-> SrcSpan
-> CompiledByteCode
-> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
loadDecls Interp
interp HscEnv
hsc_env SrcSpan
span cbc :: CompiledByteCode
cbc@CompiledByteCode{[UnlinkedBCO]
[FFIInfo]
Maybe ModBreaks
AddrEnv
ItblEnv
bc_bcos :: [UnlinkedBCO]
bc_itbls :: ItblEnv
bc_ffis :: [FFIInfo]
bc_strs :: AddrEnv
bc_breaks :: Maybe ModBreaks
bc_bcos :: CompiledByteCode -> [UnlinkedBCO]
bc_itbls :: CompiledByteCode -> ItblEnv
bc_ffis :: CompiledByteCode -> [FFIInfo]
bc_strs :: CompiledByteCode -> AddrEnv
bc_breaks :: CompiledByteCode -> Maybe ModBreaks
..} = 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
      
      (LoaderState
pls, SuccessFlag
ok, [Linkable]
links_needed, PkgsLoaded
units_needed) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls0 SrcSpan
span [Module]
needed_mods
      if SuccessFlag -> Bool
failed SuccessFlag
ok
        then GhcException
-> IO
     (LoaderState, ([(Name, ForeignHValue)], [Linkable], PkgsLoaded))
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"")
        else do
          
          let le :: LinkerEnv
le  = LoaderState -> LinkerEnv
linker_env LoaderState
pls
              le2 :: LinkerEnv
le2 = LinkerEnv
le { itbl_env :: ItblEnv
itbl_env = ItblEnv -> ItblEnv -> ItblEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv (LinkerEnv -> ItblEnv
itbl_env LinkerEnv
le) ItblEnv
bc_itbls
                       , addr_env :: AddrEnv
addr_env = AddrEnv -> AddrEnv -> AddrEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv (LinkerEnv -> AddrEnv
addr_env LinkerEnv
le) AddrEnv
bc_strs }
          
          BCOOpts
bco_opts <- DynFlags -> IO BCOOpts
initBCOOpts (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
          [(Name, HValueRef)]
new_bindings <- BCOOpts
-> Interp
-> LinkerEnv
-> [CompiledByteCode]
-> IO [(Name, HValueRef)]
linkSomeBCOs BCOOpts
bco_opts Interp
interp LinkerEnv
le2 [CompiledByteCode
cbc]
          [(Name, ForeignHValue)]
nms_fhvs <- Interp -> [(Name, HValueRef)] -> IO [(Name, ForeignHValue)]
makeForeignNamedHValueRefs Interp
interp [(Name, HValueRef)]
new_bindings
          let ce2 :: ClosureEnv
ce2  = ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv
extendClosureEnv (LinkerEnv -> ClosureEnv
closure_env LinkerEnv
le2) [(Name, ForeignHValue)]
nms_fhvs
              !pls2 :: LoaderState
pls2 = LoaderState
pls { linker_env :: LinkerEnv
linker_env = LinkerEnv
le2 { closure_env :: ClosureEnv
closure_env = ClosureEnv
ce2 } }
          (LoaderState, ([(Name, ForeignHValue)], [Linkable], PkgsLoaded))
-> IO
     (LoaderState, ([(Name, ForeignHValue)], [Linkable], PkgsLoaded))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls2, ([(Name, ForeignHValue)]
nms_fhvs, [Linkable]
links_needed, PkgsLoaded
units_needed))
  where
    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
$
      (UnlinkedBCO -> UniqDSet Name -> UniqDSet Name)
-> UniqDSet Name -> [UnlinkedBCO] -> UniqDSet Name
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (UniqDSet Name -> UniqDSet Name -> UniqDSet Name
forall a. UniqDSet a -> UniqDSet a -> UniqDSet a
unionUniqDSets (UniqDSet Name -> UniqDSet Name -> UniqDSet Name)
-> (UnlinkedBCO -> UniqDSet Name)
-> UnlinkedBCO
-> UniqDSet Name
-> UniqDSet Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnlinkedBCO -> UniqDSet Name
bcoFreeNames) UniqDSet Name
forall a. UniqDSet a
emptyUniqDSet [UnlinkedBCO]
bc_bcos
    needed_mods :: [Module]
    needed_mods :: [Module]
needed_mods = [ (() :: Constraint) => 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
    (LoaderState
pls', SuccessFlag
ok, [Linkable]
_, PkgsLoaded
_) <- Interp
-> HscEnv
-> LoaderState
-> SrcSpan
-> [Module]
-> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded)
loadDependencies Interp
interp HscEnv
hsc_env LoaderState
pls SrcSpan
noSrcSpan [Module
mod]
    if SuccessFlag -> Bool
failed SuccessFlag
ok
      then GhcException -> IO LoaderState
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError String
"could not load module")
      else LoaderState -> IO LoaderState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LoaderState
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  
        let ([Linkable]
objs, [Linkable]
bcos) = (Linkable -> Bool) -> [Linkable] -> ([Linkable], [Linkable])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Linkable -> Bool
isObjectLinkable
                              ((Linkable -> [Linkable]) -> [Linkable] -> [Linkable]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Linkable -> [Linkable]
partitionLinkable [Linkable]
linkables)
        BCOOpts
bco_opts <- DynFlags -> IO BCOOpts
initBCOOpts (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
                
        (LoaderState
pls1, SuccessFlag
ok_flag) <- Interp
-> HscEnv
-> LoaderState
-> [Linkable]
-> IO (LoaderState, SuccessFlag)
loadObjects Interp
interp HscEnv
hsc_env LoaderState
pls [Linkable]
objs
        if SuccessFlag -> Bool
failed SuccessFlag
ok_flag then
                (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls1, SuccessFlag
Failed)
          else do
                LoaderState
pls2 <- BCOOpts -> Interp -> LoaderState -> [Linkable] -> IO LoaderState
dynLinkBCOs BCOOpts
bco_opts Interp
interp LoaderState
pls1 [Linkable]
bcos
                (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls2, SuccessFlag
Succeeded)
partitionLinkable :: Linkable -> [Linkable]
partitionLinkable :: Linkable -> [Linkable]
partitionLinkable Linkable
li
   = let li_uls :: [Unlinked]
li_uls = Linkable -> [Unlinked]
linkableUnlinked Linkable
li
         li_uls_obj :: [Unlinked]
li_uls_obj = (Unlinked -> Bool) -> [Unlinked] -> [Unlinked]
forall a. (a -> Bool) -> [a] -> [a]
filter Unlinked -> Bool
isObject [Unlinked]
li_uls
         li_uls_bco :: [Unlinked]
li_uls_bco = (Unlinked -> Bool) -> [Unlinked] -> [Unlinked]
forall a. (a -> Bool) -> [a] -> [a]
filter Unlinked -> Bool
isInterpretable [Unlinked]
li_uls
     in
         case ([Unlinked]
li_uls_obj, [Unlinked]
li_uls_bco) of
            (Unlinked
_:[Unlinked]
_, Unlinked
_:[Unlinked]
_) -> [Linkable
li {linkableUnlinked :: [Unlinked]
linkableUnlinked=[Unlinked]
li_uls_obj},
                           Linkable
li {linkableUnlinked :: [Unlinked]
linkableUnlinked=[Unlinked]
li_uls_bco}]
            ([Unlinked], [Unlinked])
_ -> [Linkable
li]
findModuleLinkable_maybe :: LinkableSet -> Module -> Maybe Linkable
findModuleLinkable_maybe :: LinkableSet -> Module -> Maybe Linkable
findModuleLinkable_maybe = LinkableSet -> Module -> Maybe Linkable
forall a. ModuleEnv a -> Module -> Maybe a
lookupModuleEnv
linkableInSet :: Linkable -> LinkableSet -> Bool
linkableInSet :: Linkable -> LinkableSet -> Bool
linkableInSet Linkable
l LinkableSet
objs_loaded =
  case LinkableSet -> Module -> Maybe Linkable
findModuleLinkable_maybe 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 :: LinkableSet
objs_loaded = LinkableSet
objs_loaded' }
            unlinkeds :: [Unlinked]
unlinkeds                = (Linkable -> [Unlinked]) -> [Linkable] -> [Unlinked]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Linkable -> [Unlinked]
linkableUnlinked [Linkable]
new_objs
            wanted_objs :: [String]
wanted_objs              = (Unlinked -> String) -> [Unlinked] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Unlinked -> String
nameOfObject [Unlinked]
unlinkeds
        if Interp -> Bool
interpreterDynamic Interp
interp
            then do LoaderState
pls2 <- Interp -> HscEnv -> LoaderState -> [String] -> IO LoaderState
dynLoadObjs Interp
interp HscEnv
hsc_env LoaderState
pls1 [String]
wanted_objs
                    (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls2, SuccessFlag
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
                    
                    SuccessFlag
ok <- Interp -> IO SuccessFlag
resolveObjs Interp
interp
                    
                    
                    if SuccessFlag -> Bool
succeeded SuccessFlag
ok then
                            (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls1, SuccessFlag
Succeeded)
                      else do
                            LoaderState
pls2 <- Interp -> [Linkable] -> LoaderState -> IO LoaderState
unload_wkr Interp
interp [] LoaderState
pls1
                            (LoaderState, SuccessFlag) -> IO (LoaderState, SuccessFlag)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls2, SuccessFlag
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 ]
    (String
soFile, String
libPath , String
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
dflags2 = DynFlags
dflags {
                      
                      
                      
                      
                      
                      
                      ldInputs :: [Option]
ldInputs =
                           (String -> [Option]) -> [String] -> [Option]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\String
l -> [ String -> Option
Option (String
"-l" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l) ])
                                     ([String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String, String) -> String
forall a b. (a, b) -> b
snd ((String, String) -> String) -> [(String, String)] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(String, String)]
temp_sos)
                        [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> [Option]) -> [String] -> [Option]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
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 [])
                                     ([String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String, String) -> String
forall a b. (a, b) -> a
fst ((String, String) -> String) -> [(String, String)] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(String, String)]
temp_sos)
                        [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> [Option]) -> [String] -> [Option]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
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 [])
                             [String]
minus_big_ls
                        
                        [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map (\String
l -> String -> Option
Option (String
"-l" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l)) [String]
minus_ls,
                      
                      
                      
                      
                      
                      
                      
                      
                      
                      targetWays_ :: Ways
targetWays_ = Way -> Ways
forall a. a -> Set a
Set.singleton Way
WayDyn,
                      outputFile_ :: Maybe String
outputFile_ = String -> Maybe String
forall a. a -> Maybe a
Just String
soFile
                  }
    
    
    
    Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkDynLib Logger
logger TmpFs
tmpfs DynFlags
dflags2 UnitEnv
unit_env [String]
objs (LoadedPkgInfo -> UnitId
loaded_pkg_uid (LoadedPkgInfo -> UnitId) -> [LoadedPkgInfo] -> [UnitId]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PkgsLoaded -> [LoadedPkgInfo]
forall key elt. UniqDFM key elt -> [elt]
eltsUDFM PkgsLoaded
pkgs_loaded)
    
    TmpFs -> TempFileLifetime -> [String] -> IO ()
changeTempFilesLifetime TmpFs
tmpfs TempFileLifetime
TFL_GhcSession [String
soFile]
    Maybe String
m <- Interp -> String -> IO (Maybe String)
loadDLL Interp
interp String
soFile
    case Maybe String
m of
        Maybe String
Nothing -> 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 :: [(String, String)]
temp_sos = (String
libPath, String
libName) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
: [(String, String)]
temp_sos }
        Just 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 :: BCOOpts -> Interp -> LoaderState -> [Linkable] -> IO LoaderState
dynLinkBCOs :: BCOOpts -> Interp -> LoaderState -> [Linkable] -> IO LoaderState
dynLinkBCOs BCOOpts
bco_opts 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 :: LinkableSet
bcos_loaded = LinkableSet
bcos_loaded' }
            unlinkeds :: [Unlinked]
            unlinkeds :: [Unlinked]
unlinkeds                = (Linkable -> [Unlinked]) -> [Linkable] -> [Unlinked]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Linkable -> [Unlinked]
linkableUnlinked [Linkable]
new_bcos
            cbcs :: [CompiledByteCode]
            cbcs :: [CompiledByteCode]
cbcs      = (Unlinked -> CompiledByteCode) -> [Unlinked] -> [CompiledByteCode]
forall a b. (a -> b) -> [a] -> [b]
map Unlinked -> CompiledByteCode
byteCodeOfObject [Unlinked]
unlinkeds
            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 :: ItblEnv
itbl_env = ItblEnv
ie2, addr_env :: AddrEnv
addr_env = AddrEnv
ae2 }
        [(Name, HValueRef)]
names_and_refs <- BCOOpts
-> Interp
-> LinkerEnv
-> [CompiledByteCode]
-> IO [(Name, HValueRef)]
linkSomeBCOs BCOOpts
bco_opts Interp
interp LinkerEnv
le2 [CompiledByteCode]
cbcs
        
        let ([(Name, HValueRef)]
to_add, [(Name, HValueRef)]
to_drop) = ((Name, HValueRef) -> Bool)
-> [(Name, HValueRef)]
-> ([(Name, HValueRef)], [(Name, HValueRef)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (Name -> Bool
isExternalName(Name -> Bool)
-> ((Name, HValueRef) -> Name) -> (Name, HValueRef) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Name, HValueRef) -> Name
forall a b. (a, b) -> a
fst) [(Name, HValueRef)]
names_and_refs
        
        Interp -> [HValueRef] -> IO ()
freeHValueRefs Interp
interp (((Name, HValueRef) -> HValueRef)
-> [(Name, HValueRef)] -> [HValueRef]
forall a b. (a -> b) -> [a] -> [b]
map (Name, HValueRef) -> HValueRef
forall a b. (a, b) -> b
snd [(Name, HValueRef)]
to_drop)
        
        [(Name, ForeignHValue)]
new_binds <- Interp -> [(Name, HValueRef)] -> IO [(Name, ForeignHValue)]
makeForeignNamedHValueRefs Interp
interp [(Name, HValueRef)]
to_add
        let ce2 :: ClosureEnv
ce2 = ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv
extendClosureEnv (LinkerEnv -> ClosureEnv
closure_env LinkerEnv
le2) [(Name, ForeignHValue)]
new_binds
        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
pls1 { linker_env :: LinkerEnv
linker_env = LinkerEnv
le2 { closure_env :: ClosureEnv
closure_env = ClosureEnv
ce2 } }
linkSomeBCOs :: BCOOpts
             -> Interp
             -> LinkerEnv
             -> [CompiledByteCode]
             -> IO [(Name,HValueRef)]
                        
                        
                        
linkSomeBCOs :: BCOOpts
-> Interp
-> LinkerEnv
-> [CompiledByteCode]
-> IO [(Name, HValueRef)]
linkSomeBCOs BCOOpts
bco_opts Interp
interp LinkerEnv
le [CompiledByteCode]
mods = (CompiledByteCode
 -> ([(RemoteRef BreakArray, [UnlinkedBCO])]
     -> IO [(Name, HValueRef)])
 -> [(RemoteRef BreakArray, [UnlinkedBCO])]
 -> IO [(Name, HValueRef)])
-> ([(RemoteRef BreakArray, [UnlinkedBCO])]
    -> IO [(Name, HValueRef)])
-> [CompiledByteCode]
-> [(RemoteRef BreakArray, [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
-> ([(RemoteRef BreakArray, [UnlinkedBCO])]
    -> IO [(Name, HValueRef)])
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
-> IO [(Name, HValueRef)]
forall {b}.
CompiledByteCode
-> ([(RemoteRef BreakArray, [UnlinkedBCO])] -> IO b)
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
-> IO b
fun [(RemoteRef BreakArray, [UnlinkedBCO])] -> IO [(Name, HValueRef)]
do_link [CompiledByteCode]
mods []
 where
  fun :: CompiledByteCode
-> ([(RemoteRef BreakArray, [UnlinkedBCO])] -> IO b)
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
-> IO b
fun CompiledByteCode{[UnlinkedBCO]
[FFIInfo]
Maybe ModBreaks
AddrEnv
ItblEnv
bc_bcos :: CompiledByteCode -> [UnlinkedBCO]
bc_itbls :: CompiledByteCode -> ItblEnv
bc_ffis :: CompiledByteCode -> [FFIInfo]
bc_strs :: CompiledByteCode -> AddrEnv
bc_breaks :: CompiledByteCode -> Maybe ModBreaks
bc_bcos :: [UnlinkedBCO]
bc_itbls :: ItblEnv
bc_ffis :: [FFIInfo]
bc_strs :: AddrEnv
bc_breaks :: Maybe ModBreaks
..} [(RemoteRef BreakArray, [UnlinkedBCO])] -> IO b
inner [(RemoteRef BreakArray, [UnlinkedBCO])]
accum =
    case Maybe ModBreaks
bc_breaks of
      Maybe ModBreaks
Nothing -> [(RemoteRef BreakArray, [UnlinkedBCO])] -> IO b
inner ((String -> RemoteRef BreakArray
forall a. String -> a
panic String
"linkSomeBCOs: no break array", [UnlinkedBCO]
bc_bcos) (RemoteRef BreakArray, [UnlinkedBCO])
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
forall a. a -> [a] -> [a]
: [(RemoteRef BreakArray, [UnlinkedBCO])]
accum)
      Just ModBreaks
mb -> ForeignRef BreakArray -> (RemoteRef BreakArray -> IO b) -> IO b
forall a b. ForeignRef a -> (RemoteRef a -> IO b) -> IO b
withForeignRef (ModBreaks -> ForeignRef BreakArray
modBreaks_flags ModBreaks
mb) ((RemoteRef BreakArray -> IO b) -> IO b)
-> (RemoteRef BreakArray -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \RemoteRef BreakArray
breakarray ->
                   [(RemoteRef BreakArray, [UnlinkedBCO])] -> IO b
inner ((RemoteRef BreakArray
breakarray, [UnlinkedBCO]
bc_bcos) (RemoteRef BreakArray, [UnlinkedBCO])
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
-> [(RemoteRef BreakArray, [UnlinkedBCO])]
forall a. a -> [a] -> [a]
: [(RemoteRef BreakArray, [UnlinkedBCO])]
accum)
  do_link :: [(RemoteRef BreakArray, [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 [(RemoteRef BreakArray, [UnlinkedBCO])]
mods = do
    let flat :: [(RemoteRef BreakArray, UnlinkedBCO)]
flat = [ (RemoteRef BreakArray
breakarray, UnlinkedBCO
bco) | (RemoteRef BreakArray
breakarray, [UnlinkedBCO]
bcos) <- [(RemoteRef BreakArray, [UnlinkedBCO])]
mods, UnlinkedBCO
bco <- [UnlinkedBCO]
bcos ]
        names :: [Name]
names = ((RemoteRef BreakArray, UnlinkedBCO) -> Name)
-> [(RemoteRef BreakArray, UnlinkedBCO)] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (UnlinkedBCO -> Name
unlinkedBCOName (UnlinkedBCO -> Name)
-> ((RemoteRef BreakArray, UnlinkedBCO) -> UnlinkedBCO)
-> (RemoteRef BreakArray, UnlinkedBCO)
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RemoteRef BreakArray, UnlinkedBCO) -> UnlinkedBCO
forall a b. (a, b) -> b
snd) [(RemoteRef BreakArray, 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..])
    [ResolvedBCO]
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
-> LinkerEnv
-> NameEnv Int
-> RemoteRef BreakArray
-> UnlinkedBCO
-> IO ResolvedBCO
linkBCO Interp
interp LinkerEnv
le NameEnv Int
bco_ix RemoteRef BreakArray
breakarray UnlinkedBCO
bco
                         | (RemoteRef BreakArray
breakarray, UnlinkedBCO
bco) <- [(RemoteRef BreakArray, UnlinkedBCO)]
flat ]
    [HValueRef]
hvrefs <- Interp -> BCOOpts -> [ResolvedBCO] -> IO [HValueRef]
createBCOs Interp
interp BCOOpts
bco_opts [ResolvedBCO]
resolved
    [(Name, HValueRef)] -> IO [(Name, HValueRef)]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name] -> [HValueRef] -> [(Name, HValueRef)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
names [HValueRef]
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
        LoaderState
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
                 LoaderState
pls1 <- Interp -> [Linkable] -> LoaderState -> IO LoaderState
unload_wkr Interp
interp [Linkable]
linkables LoaderState
pls
                 (LoaderState, LoaderState) -> IO (LoaderState, LoaderState)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LoaderState
pls1, LoaderState
pls1)
        let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
        Logger -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger Int
3 (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$
          String -> SDoc
text String
"unload: retaining objs" SDoc -> SDoc -> SDoc
<+> [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
new_pls)
        Logger -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger Int
3 (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$
          String -> SDoc
text String
"unload: retaining bcos" SDoc -> SDoc -> SDoc
<+> [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
new_pls)
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
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
isObjectLinkable [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
&&
                    (() :: Constraint) => 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 :: LinkerEnv
linker_env = (Name -> Bool) -> LinkerEnv -> LinkerEnv
filterLinkerEnv Name -> Bool
keep_name LinkerEnv
linker_env,
                       bcos_loaded :: LinkableSet
bcos_loaded = LinkableSet
remaining_bcos_loaded,
                       objs_loaded :: LinkableSet
objs_loaded = LinkableSet
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) [String
f | DotO String
f <- Linkable -> [Unlinked]
linkableUnlinked 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
    PkgsLoaded
pkgs' <- PkgsLoaded -> [UnitId] -> IO PkgsLoaded
link (LoaderState -> PkgsLoaded
pkgs_loaded LoaderState
pls) [UnitId]
new_pks
    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 { pkgs_loaded :: PkgsLoaded
pkgs_loaded = PkgsLoaded
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 ((() :: Constraint) => 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
               
             ; PkgsLoaded
pkgs' <- PkgsLoaded -> [UnitId] -> IO PkgsLoaded
link PkgsLoaded
pkgs [UnitId]
deps
                
             ; ([LibrarySpec]
hs_cls, [LibrarySpec]
extra_cls) <- Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec])
loadPackage Interp
interp HscEnv
hsc_env UnitInfo
pkg_cfg
             ; let trans_deps :: UniqDSet UnitId
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)
                                                   ]
             ; PkgsLoaded -> IO PkgsLoaded
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PkgsLoaded -> UnitId -> LoadedPkgInfo -> PkgsLoaded
forall key elt.
Uniquable key =>
UniqDFM key elt -> key -> elt -> UniqDFM key elt
addToUDFM PkgsLoaded
pkgs' UnitId
new_pkg (UnitId
-> [LibrarySpec]
-> [LibrarySpec]
-> UniqDSet UnitId
-> LoadedPkgInfo
LoadedPkgInfo UnitId
new_pkg [LibrarySpec]
hs_cls [LibrarySpec]
extra_cls UniqDSet UnitId
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])
loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec])
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
        
        [String]
gcc_paths <- Logger -> DynFlags -> OS -> IO [String]
getGCCPaths Logger
logger DynFlags
dflags (Platform -> OS
platformOS Platform
platform)
        [String]
dirs_env <- String -> [String] -> IO [String]
addEnvPaths String
"LIBRARY_PATH" [String]
dirs
        [LibrarySpec]
hs_classifieds
           <- (String -> IO LibrarySpec) -> [String] -> IO [LibrarySpec]
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 (Interp
-> HscEnv
-> Bool
-> [String]
-> [String]
-> String
-> IO LibrarySpec
locateLib Interp
interp HscEnv
hsc_env Bool
True  [String]
dirs_env [String]
gcc_paths) [String]
hs_libs'
        [LibrarySpec]
extra_classifieds
           <- (String -> IO LibrarySpec) -> [String] -> IO [LibrarySpec]
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 (Interp
-> HscEnv
-> Bool
-> [String]
-> [String]
-> String
-> IO LibrarySpec
locateLib Interp
interp HscEnv
hsc_env Bool
False [String]
dirs_env [String]
gcc_paths) [String]
extra_libs
        let classifieds :: [LibrarySpec]
classifieds = [LibrarySpec]
hs_classifieds [LibrarySpec] -> [LibrarySpec] -> [LibrarySpec]
forall a. [a] -> [a] -> [a]
++ [LibrarySpec]
extra_classifieds
        
        let known_dlls :: [String]
known_dlls = [ String
dll  | DLLPath String
dll    <- [LibrarySpec]
classifieds ]
#if defined(CAN_LOAD_DLL)
            dlls :: [String]
dlls       = [ String
dll  | DLL String
dll        <- [LibrarySpec]
classifieds ]
#endif
            objs :: [String]
objs       = [ String
obj  | Objects [String]
objs    <- [LibrarySpec]
classifieds
                                , String
obj <- [String]
objs ]
            archs :: [String]
archs      = [ String
arch | Archive String
arch   <- [LibrarySpec]
classifieds ]
        
        let dll_paths :: [String]
dll_paths  = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
takeDirectory [String]
known_dlls
            all_paths :: [String]
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
        [String]
all_paths_env <- String -> [String] -> IO [String]
addEnvPaths String
"LD_LIBRARY_PATH" [String]
all_paths
        [Ptr ()]
pathCache <- (String -> IO (Ptr ())) -> [String] -> IO [Ptr ()]
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 (Interp -> String -> IO (Ptr ())
addLibrarySearchPath Interp
interp) [String]
all_paths_env
        Logger -> SDoc -> IO ()
maybePutSDoc Logger
logger
            (String -> SDoc
text String
"Loading unit " SDoc -> SDoc -> SDoc
<> UnitInfo -> SDoc
pprUnitInfoForUser UnitInfo
pkg SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
" ... ")
#if defined(CAN_LOAD_DLL)
        Interp -> Platform -> UnitInfo -> IO ()
loadFrameworks Interp
interp Platform
platform UnitInfo
pkg
        
        
        (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> HscEnv -> Bool -> String -> IO ()
load_dyn Interp
interp HscEnv
hsc_env Bool
True) [String]
known_dlls
        
        
        (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> HscEnv -> Bool -> String -> IO ()
load_dyn Interp
interp HscEnv
hsc_env (Bool -> Bool
not Bool
is_dyn) (String -> IO ()) -> (String -> String) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Platform -> String -> String
platformSOName Platform
platform) [String]
dlls
#endif
        
        
        
        (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]
objs
        (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> String -> IO ()
loadArchive Interp
interp) [String]
archs
        Logger -> String -> IO ()
maybePutStr Logger
logger String
"linking ... "
        SuccessFlag
ok <- Interp -> IO SuccessFlag
resolveObjs Interp
interp
        
        
        
        
        (Ptr () -> IO Bool) -> [Ptr ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Interp -> Ptr () -> IO Bool
removeLibrarySearchPath Interp
interp) ([Ptr ()] -> IO ()) -> [Ptr ()] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Ptr ()] -> [Ptr ()]
forall a. [a] -> [a]
reverse [Ptr ()]
pathCache
        if SuccessFlag -> Bool
succeeded SuccessFlag
ok
           then do
             Logger -> String -> IO ()
maybePutStrLn Logger
logger String
"done."
             ([LibrarySpec], [LibrarySpec]) -> IO ([LibrarySpec], [LibrarySpec])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([LibrarySpec]
hs_classifieds, [LibrarySpec]
extra_classifieds)
           else let errmsg :: SDoc
errmsg = String -> SDoc
text String
"unable to load unit `"
                             SDoc -> SDoc -> SDoc
<> UnitInfo -> SDoc
pprUnitInfoForUser UnitInfo
pkg SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"'"
                 in GhcException -> IO ([LibrarySpec], [LibrarySpec])
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
InstallationError (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags SDoc
errmsg))
#if defined(CAN_LOAD_DLL)
load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO ()
load_dyn :: Interp -> HscEnv -> Bool -> String -> IO ()
load_dyn Interp
interp HscEnv
hsc_env Bool
crash_early String
dll = do
  Maybe String
r <- Interp -> String -> IO (Maybe String)
loadDLL Interp
interp String
dll
  case Maybe String
r of
    Maybe String
Nothing  -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    Just String
err ->
      if Bool
crash_early
        then String -> IO ()
forall a. String -> IO a
cmdLineErrorIO String
err
        else
          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 -> MessageClass
mkMCDiagnostic DiagOpts
diag_opts (DiagnosticReason -> MessageClass)
-> DiagnosticReason -> MessageClass
forall a b. (a -> b) -> a -> b
$ WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnMissedExtraSharedLib)
                  SrcSpan
noSrcSpan (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle (String -> SDoc
note String
err)
  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 -> SDoc
note String
err = [SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ (String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
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  Maybe String
r <- Interp -> [String] -> String -> IO (Maybe String)
loadFramework Interp
interp [String]
fw_dirs String
fw
                  case Maybe String
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]
++ 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 -> MessageClass
mkMCDiagnostic DiagOpts
diag_opts DiagnosticReason
WarningWithoutFlag
          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
text String
"Interpreter failed to load profiled static library" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
lib SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'.' SDoc -> SDoc -> SDoc
$$
              String -> SDoc
text String
" \tTrying dynamic library instead. If this fails try to rebuild" SDoc -> SDoc -> SDoc
<+>
              String -> SDoc
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 Maybe a
x' <- IO (Maybe a)
x
                       if Maybe a -> Bool
forall a. Maybe a -> Bool
isJust Maybe a
x'
                          then Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
x'
                          else [IO (Maybe a)] -> IO (Maybe a)
forall a. [IO (Maybe a)] -> IO (Maybe a)
apply [IO (Maybe a)]
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
   
   
   String
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 :: String
file = case String -> [String]
lines String
str of
                []  -> String
""
                String
l:[String]
_ -> String
l
   if (String
file String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
so)
      then Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
      else do Bool
b <- String -> IO Bool
doesFileExist String
file 
              Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (if Bool
b then String -> Maybe String
forall a. a -> Maybe a
Just String
file else Maybe String
forall a. Maybe a
Nothing)
getGCCPaths :: Logger -> DynFlags -> OS -> IO [FilePath]
getGCCPaths :: Logger -> DynFlags -> OS -> IO [String]
getGCCPaths Logger
logger DynFlags
dflags OS
os
  = case OS
os of
      OS
OSMinGW32 ->
        do [String]
gcc_dirs <- Logger -> DynFlags -> String -> IO [String]
getGccSearchDirectory Logger
logger DynFlags
dflags String
"libraries"
           [String]
sys_dirs <- IO [String]
getSystemDirectories
           [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] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
gcc_dirs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
sys_dirs
      OS
_         -> [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
    [(String, [String])]
cache <- IORef [(String, [String])] -> IO [(String, [String])]
forall a. IORef a -> IO a
readIORef IORef [(String, [String])]
gccSearchDirCache
    case String -> [(String, [String])] -> Maybe [String]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
key [(String, [String])]
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
        String
str <- Logger -> DynFlags -> [Option] -> IO String
askLd Logger
logger DynFlags
dflags [String -> Option
Option String
"--print-search-dirs"]
        let line :: String
line = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
str
            name :: String
name = String
key String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": ="
        if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
line
          then [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
          else do let val :: [String]
val = String -> [String]
split (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String -> String -> String
find String
name String
line
                  [String]
dirs <- (String -> IO Bool) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
doesDirectoryExist [String]
val
                  IORef [(String, [String])]
-> ([(String, [String])] -> [(String, [String])]) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef [(String, [String])]
gccSearchDirCache ((String
key, [String]
dirs)(String, [String]) -> [(String, [String])] -> [(String, [String])]
forall a. a -> [a] -> [a]
:)
                  [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
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 -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==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 if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
val
                             then []
                             else 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] -> String
forall a. HasCallStack => [a] -> a
head [String]
val) 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 
       
       
       String
working_dir <- IO String
getCurrentDirectory
       Maybe String
values <- String -> IO (Maybe String)
lookupEnv String
name
       case Maybe String
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
text String
s)
maybePutStrLn :: Logger -> String -> IO ()
maybePutStrLn :: Logger -> String -> IO ()
maybePutStrLn Logger
logger String
s = Logger -> SDoc -> IO ()
maybePutSDoc Logger
logger (String -> SDoc
text String
s SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"\n")