module GHC.Runtime.Linker.Types (
DynLinker(..),
PersistentLinkerState(..),
Linkable(..),
Unlinked(..),
SptEntry(..)
) where
import GHC.Prelude ( FilePath, String, show )
import Data.Time ( UTCTime )
import Data.Maybe ( Maybe )
import Control.Concurrent.MVar ( MVar )
import GHC.Unit ( UnitId, Module )
import GHC.ByteCode.Types ( ItblEnv, CompiledByteCode )
import GHC.Utils.Outputable
import GHC.Types.Var ( Id )
import GHC.Fingerprint.Type ( Fingerprint )
import GHC.Types.Name.Env ( NameEnv )
import GHC.Types.Name ( Name )
import GHCi.RemoteTypes ( ForeignHValue )
type ClosureEnv = NameEnv (Name, ForeignHValue)
newtype DynLinker =
DynLinker { DynLinker -> MVar (Maybe PersistentLinkerState)
dl_mpls :: MVar (Maybe PersistentLinkerState) }
data PersistentLinkerState
= PersistentLinkerState {
PersistentLinkerState -> ClosureEnv
closure_env :: ClosureEnv,
PersistentLinkerState -> ItblEnv
itbl_env :: !ItblEnv,
PersistentLinkerState -> [Linkable]
bcos_loaded :: ![Linkable],
PersistentLinkerState -> [Linkable]
objs_loaded :: ![Linkable],
PersistentLinkerState -> [UnitId]
pkgs_loaded :: ![UnitId],
PersistentLinkerState -> [(FilePath, FilePath)]
temp_sos :: ![(FilePath, String)] }
data Linkable = LM {
Linkable -> UTCTime
linkableTime :: UTCTime,
Linkable -> Module
linkableModule :: Module,
Linkable -> [Unlinked]
linkableUnlinked :: [Unlinked]
}
instance Outputable Linkable where
ppr :: Linkable -> SDoc
ppr (LM UTCTime
when_made Module
mod [Unlinked]
unlinkeds)
= (FilePath -> SDoc
text FilePath
"LinkableM" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (FilePath -> SDoc
text (UTCTime -> FilePath
forall a. Show a => a -> FilePath
show UTCTime
when_made)) SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod)
SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
3 ([Unlinked] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Unlinked]
unlinkeds)
data Unlinked
= DotO FilePath
| DotA FilePath
| DotDLL FilePath
| BCOs CompiledByteCode
[SptEntry]
instance Outputable Unlinked where
ppr :: Unlinked -> SDoc
ppr (DotO FilePath
path) = FilePath -> SDoc
text FilePath
"DotO" SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
path
ppr (DotA FilePath
path) = FilePath -> SDoc
text FilePath
"DotA" SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
path
ppr (DotDLL FilePath
path) = FilePath -> SDoc
text FilePath
"DotDLL" SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
path
ppr (BCOs CompiledByteCode
bcos [SptEntry]
spt) = FilePath -> SDoc
text FilePath
"BCOs" SDoc -> SDoc -> SDoc
<+> CompiledByteCode -> SDoc
forall a. Outputable a => a -> SDoc
ppr CompiledByteCode
bcos SDoc -> SDoc -> SDoc
<+> [SptEntry] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [SptEntry]
spt
data SptEntry = SptEntry Id Fingerprint
instance Outputable SptEntry where
ppr :: SptEntry -> SDoc
ppr (SptEntry Id
id Fingerprint
fpr) = Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr Id
id SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<+> Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
fpr