never executed always true always false
    1 -----------------------------------------------------------------------------
    2 --
    3 -- Types for the linkers and the loader
    4 --
    5 -- (c) The University of Glasgow 2019
    6 --
    7 -----------------------------------------------------------------------------
    8 
    9 module GHC.Linker.Types
   10    ( Loader (..)
   11    , LoaderState (..)
   12    , uninitializedLoader
   13    , Linkable(..)
   14    , Unlinked(..)
   15    , SptEntry(..)
   16    , isObjectLinkable
   17    , linkableObjs
   18    , isObject
   19    , nameOfObject
   20    , nameOfObject_maybe
   21    , isInterpretable
   22    , byteCodeOfObject
   23    , LibrarySpec(..)
   24    )
   25 where
   26 
   27 import GHC.Prelude
   28 import GHC.Unit                ( UnitId, Module, ModuleNameWithIsBoot )
   29 import GHC.ByteCode.Types      ( ItblEnv, CompiledByteCode )
   30 import GHC.Fingerprint.Type    ( Fingerprint )
   31 import GHCi.RemoteTypes        ( ForeignHValue )
   32 
   33 import GHC.Types.Var           ( Id )
   34 import GHC.Types.Name.Env      ( NameEnv )
   35 import GHC.Types.Name          ( Name )
   36 
   37 import GHC.Utils.Outputable
   38 import GHC.Utils.Panic
   39 
   40 import Control.Concurrent.MVar
   41 import Data.Time               ( UTCTime )
   42 import Data.Maybe
   43 import qualified Data.Map as M
   44 
   45 
   46 {- **********************************************************************
   47 
   48                         The Loader's state
   49 
   50   ********************************************************************* -}
   51 
   52 {-
   53 The loader state *must* match the actual state of the C dynamic linker at all
   54 times.
   55 
   56 The MVar used to hold the LoaderState contains a Maybe LoaderState. The MVar
   57 serves to ensure mutual exclusion between multiple loaded copies of the GHC
   58 library. The Maybe may be Nothing to indicate that the linker has not yet been
   59 initialised.
   60 
   61 The LoaderState maps Names to actual closures (for interpreted code only), for
   62 use during linking.
   63 -}
   64 
   65 newtype Loader = Loader { loader_state :: MVar (Maybe LoaderState) }
   66 
   67 data LoaderState = LoaderState
   68     { closure_env :: ClosureEnv
   69         -- ^ Current global mapping from Names to their true values
   70 
   71     , itbl_env    :: !ItblEnv
   72         -- ^ The current global mapping from RdrNames of DataCons to
   73         -- info table addresses.
   74         -- When a new Unlinked is linked into the running image, or an existing
   75         -- module in the image is replaced, the itbl_env must be updated
   76         -- appropriately.
   77 
   78     , bcos_loaded :: ![Linkable]
   79         -- ^ The currently loaded interpreted modules (home package)
   80 
   81     , objs_loaded :: ![Linkable]
   82         -- ^ And the currently-loaded compiled modules (home package)
   83 
   84     , pkgs_loaded :: ![UnitId]
   85         -- ^ The currently-loaded packages; always object code
   86         -- Held, as usual, in dependency order; though I am not sure if
   87         -- that is really important
   88     , hs_objs_loaded :: ![LibrarySpec]
   89     , non_hs_objs_loaded :: ![LibrarySpec]
   90     , module_deps :: M.Map ModuleNameWithIsBoot [Linkable]
   91 
   92     , temp_sos :: ![(FilePath, String)]
   93         -- ^ We need to remember the name of previous temporary DLL/.so
   94         -- libraries so we can link them (see #10322)
   95     }
   96 
   97 uninitializedLoader :: IO Loader
   98 uninitializedLoader = Loader <$> newMVar Nothing
   99 
  100 type ClosureEnv = NameEnv (Name, ForeignHValue)
  101 
  102 -- | Information we can use to dynamically link modules into the compiler
  103 data Linkable = LM {
  104   linkableTime     :: !UTCTime,          -- ^ Time at which this linkable was built
  105                                         -- (i.e. when the bytecodes were produced,
  106                                         --       or the mod date on the files)
  107   linkableModule   :: !Module,           -- ^ The linkable module itself
  108   linkableUnlinked :: [Unlinked]
  109     -- ^ Those files and chunks of code we have yet to link.
  110     --
  111     -- INVARIANT: A valid linkable always has at least one 'Unlinked' item.
  112  }
  113 
  114 instance Outputable Linkable where
  115   ppr (LM when_made mod unlinkeds)
  116      = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
  117        $$ nest 3 (ppr unlinkeds)
  118 
  119 -- | Objects which have yet to be linked by the compiler
  120 data Unlinked
  121   = DotO FilePath      -- ^ An object file (.o)
  122   | DotA FilePath      -- ^ Static archive file (.a)
  123   | DotDLL FilePath    -- ^ Dynamically linked library file (.so, .dll, .dylib)
  124   | BCOs CompiledByteCode
  125          [SptEntry]    -- ^ A byte-code object, lives only in memory. Also
  126                        -- carries some static pointer table entries which
  127                        -- should be loaded along with the BCOs.
  128                        -- See Note [Grant plan for static forms] in
  129                        -- "GHC.Iface.Tidy.StaticPtrTable".
  130 
  131 instance Outputable Unlinked where
  132   ppr (DotO path)   = text "DotO" <+> text path
  133   ppr (DotA path)   = text "DotA" <+> text path
  134   ppr (DotDLL path) = text "DotDLL" <+> text path
  135   ppr (BCOs bcos spt) = text "BCOs" <+> ppr bcos <+> ppr spt
  136 
  137 -- | An entry to be inserted into a module's static pointer table.
  138 -- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable".
  139 data SptEntry = SptEntry Id Fingerprint
  140 
  141 instance Outputable SptEntry where
  142   ppr (SptEntry id fpr) = ppr id <> colon <+> ppr fpr
  143 
  144 
  145 isObjectLinkable :: Linkable -> Bool
  146 isObjectLinkable l = not (null unlinked) && all isObject unlinked
  147   where unlinked = linkableUnlinked l
  148         -- A linkable with no Unlinked's is treated as a BCO.  We can
  149         -- generate a linkable with no Unlinked's as a result of
  150         -- compiling a module in NoBackend mode, and this choice
  151         -- happens to work well with checkStability in module GHC.
  152 
  153 linkableObjs :: Linkable -> [FilePath]
  154 linkableObjs l = [ f | DotO f <- linkableUnlinked l ]
  155 
  156 -------------------------------------------
  157 
  158 -- | Is this an actual file on disk we can link in somehow?
  159 isObject :: Unlinked -> Bool
  160 isObject (DotO _)   = True
  161 isObject (DotA _)   = True
  162 isObject (DotDLL _) = True
  163 isObject _          = False
  164 
  165 -- | Is this a bytecode linkable with no file on disk?
  166 isInterpretable :: Unlinked -> Bool
  167 isInterpretable = not . isObject
  168 
  169 nameOfObject_maybe :: Unlinked -> Maybe FilePath
  170 nameOfObject_maybe (DotO fn)   = Just fn
  171 nameOfObject_maybe (DotA fn)   = Just fn
  172 nameOfObject_maybe (DotDLL fn) = Just fn
  173 nameOfObject_maybe (BCOs {})   = Nothing
  174 
  175 -- | Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
  176 nameOfObject :: Unlinked -> FilePath
  177 nameOfObject o = fromMaybe (pprPanic "nameOfObject" (ppr o)) (nameOfObject_maybe o)
  178 
  179 -- | Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
  180 byteCodeOfObject :: Unlinked -> CompiledByteCode
  181 byteCodeOfObject (BCOs bc _) = bc
  182 byteCodeOfObject other       = pprPanic "byteCodeOfObject" (ppr other)
  183 
  184 {- **********************************************************************
  185 
  186                 Loading packages
  187 
  188   ********************************************************************* -}
  189 
  190 data LibrarySpec
  191    = Objects [FilePath] -- Full path names of set of .o files, including trailing .o
  192                         -- We allow batched loading to ensure that cyclic symbol
  193                         -- references can be resolved (see #13786).
  194                         -- For dynamic objects only, try to find the object
  195                         -- file in all the directories specified in
  196                         -- v_Library_paths before giving up.
  197 
  198    | Archive FilePath   -- Full path name of a .a file, including trailing .a
  199 
  200    | DLL String         -- "Unadorned" name of a .DLL/.so
  201                         --  e.g.    On unix     "qt"  denotes "libqt.so"
  202                         --          On Windows  "burble"  denotes "burble.DLL" or "libburble.dll"
  203                         --  loadDLL is platform-specific and adds the lib/.so/.DLL
  204                         --  suffixes platform-dependently
  205 
  206    | DLLPath FilePath   -- Absolute or relative pathname to a dynamic library
  207                         -- (ends with .dll or .so).
  208 
  209    | Framework String   -- Only used for darwin, but does no harm
  210 
  211 instance Outputable LibrarySpec where
  212   ppr (Objects objs) = text "Objects" <+> ppr objs
  213   ppr (Archive a) = text "Archive" <+> text a
  214   ppr (DLL s) = text "DLL" <+> text s
  215   ppr (DLLPath f) = text "DLLPath" <+> text f
  216   ppr (Framework s) = text "Framework" <+> text s