never executed always true always false
    1 
    2 -- | Linking Haskell units
    3 module GHC.Linker.Unit
    4    ( collectLinkOpts
    5    , collectArchives
    6    , getUnitLinkOpts
    7    , getLibs
    8    )
    9 where
   10 
   11 import GHC.Prelude
   12 import GHC.Platform.Ways
   13 import GHC.Unit.Types
   14 import GHC.Unit.Info
   15 import GHC.Unit.State
   16 import GHC.Unit.Env
   17 import GHC.Utils.Misc
   18 
   19 import qualified GHC.Data.ShortText as ST
   20 
   21 import GHC.Driver.Session
   22 
   23 import Control.Monad
   24 import System.Directory
   25 import System.FilePath
   26 
   27 -- | Find all the link options in these and the preload packages,
   28 -- returning (package hs lib options, extra library options, other flags)
   29 getUnitLinkOpts :: DynFlags -> UnitEnv -> [UnitId] -> IO ([String], [String], [String])
   30 getUnitLinkOpts dflags unit_env pkgs = do
   31     ps <- mayThrowUnitErr $ preloadUnitsInfo' unit_env pkgs
   32     return (collectLinkOpts dflags ps)
   33 
   34 collectLinkOpts :: DynFlags -> [UnitInfo] -> ([String], [String], [String])
   35 collectLinkOpts dflags ps =
   36     (
   37         concatMap (map ("-l" ++) . unitHsLibs (ghcNameVersion dflags) (ways dflags)) ps,
   38         concatMap (map ("-l" ++) . map ST.unpack . unitExtDepLibsSys) ps,
   39         concatMap (map ST.unpack . unitLinkerOptions) ps
   40     )
   41 
   42 collectArchives :: DynFlags -> UnitInfo -> IO [FilePath]
   43 collectArchives dflags pc =
   44   filterM doesFileExist [ searchPath </> ("lib" ++ lib ++ ".a")
   45                         | searchPath <- searchPaths
   46                         , lib <- libs ]
   47   where searchPaths = ordNub . filter notNull . libraryDirsForWay (ways dflags) $ pc
   48         libs        = unitHsLibs (ghcNameVersion dflags) (ways dflags) pc ++ map ST.unpack (unitExtDepLibsSys pc)
   49 
   50 -- | Either the 'unitLibraryDirs' or 'unitLibraryDynDirs' as appropriate for the way.
   51 libraryDirsForWay :: Ways -> UnitInfo -> [String]
   52 libraryDirsForWay ws
   53   | hasWay ws WayDyn = map ST.unpack . unitLibraryDynDirs
   54   | otherwise        = map ST.unpack . unitLibraryDirs
   55 
   56 getLibs :: DynFlags -> UnitEnv -> [UnitId] -> IO [(String,String)]
   57 getLibs dflags unit_env pkgs = do
   58   ps <- mayThrowUnitErr $ preloadUnitsInfo' unit_env pkgs
   59   fmap concat . forM ps $ \p -> do
   60     let candidates = [ (l </> f, f) | l <- collectLibraryDirs (ways dflags) [p]
   61                                     , f <- (\n -> "lib" ++ n ++ ".a") <$> unitHsLibs (ghcNameVersion dflags) (ways dflags) p ]
   62     filterM (doesFileExist . fst) candidates
   63