{-# LANGUAGE RecordWildCards, FlexibleInstances, MultiParamTypeClasses #-}

-- | Info about installed units (compiled libraries)
module GHC.Unit.Info
   ( GenericUnitInfo (..)
   , GenUnitInfo
   , UnitInfo
   , UnitKey (..)
   , UnitKeyInfo
   , mkUnitKeyInfo
   , mapUnitInfo
   , mkUnitPprInfo

   , mkUnit

   , PackageId(..)
   , PackageName(..)
   , Version(..)
   , unitPackageNameString
   , unitPackageIdString
   , pprUnitInfo

   , collectIncludeDirs
   , collectExtraCcOpts
   , collectLibraryDirs
   , collectFrameworks
   , collectFrameworksDirs
   , unitHsLibs
   )
where

import GHC.Prelude
import GHC.Platform.Ways

import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic

import GHC.Types.Unique

import GHC.Data.FastString
import qualified GHC.Data.ShortText as ST

import GHC.Unit.Module as Module
import GHC.Unit.Ppr
import GHC.Unit.Database

import GHC.Settings

import Data.Version
import Data.Bifunctor
import Data.List (isPrefixOf, stripPrefix)


-- | Information about an installed unit
--
-- We parameterize on the unit identifier:
--    * UnitKey: identifier used in the database (cf 'UnitKeyInfo')
--    * UnitId: identifier used to generate code (cf 'UnitInfo')
--
-- These two identifiers are different for wired-in packages. See Note [About
-- units] in "GHC.Unit"
type GenUnitInfo unit = GenericUnitInfo PackageId PackageName unit ModuleName (GenModule (GenUnit unit))

-- | Information about an installed unit (units are identified by their database
-- UnitKey)
type UnitKeyInfo = GenUnitInfo UnitKey

-- | Information about an installed unit (units are identified by their internal
-- UnitId)
type UnitInfo    = GenUnitInfo UnitId

-- | Convert a DbUnitInfo (read from a package database) into `UnitKeyInfo`
mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo
mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo
mkUnitKeyInfo = forall uid1 uid2 srcpkg1 srcpkg2 srcpkgname1 srcpkgname2 modname1
       modname2 mod1 mod2.
(uid1 -> uid2)
-> (srcpkg1 -> srcpkg2)
-> (srcpkgname1 -> srcpkgname2)
-> (modname1 -> modname2)
-> (mod1 -> mod2)
-> GenericUnitInfo srcpkg1 srcpkgname1 uid1 modname1 mod1
-> GenericUnitInfo srcpkg2 srcpkgname2 uid2 modname2 mod2
mapGenericUnitInfo
   ByteString -> UnitKey
mkUnitKey'
   ByteString -> PackageId
mkPackageIdentifier'
   ByteString -> PackageName
mkPackageName'
   ByteString -> ModuleName
mkModuleName'
   DbModule -> GenModule (GenUnit UnitKey)
mkModule'
   where
     mkPackageIdentifier' :: ByteString -> PackageId
mkPackageIdentifier' = FastString -> PackageId
PackageId      forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> FastString
mkFastStringByteString
     mkPackageName' :: ByteString -> PackageName
mkPackageName'       = FastString -> PackageName
PackageName    forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> FastString
mkFastStringByteString
     mkUnitKey' :: ByteString -> UnitKey
mkUnitKey'           = FastString -> UnitKey
UnitKey        forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> FastString
mkFastStringByteString
     mkModuleName' :: ByteString -> ModuleName
mkModuleName'        = FastString -> ModuleName
mkModuleNameFS forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> FastString
mkFastStringByteString
     mkVirtUnitKey' :: DbInstUnitId -> GenUnit UnitKey
mkVirtUnitKey' DbInstUnitId
i = case DbInstUnitId
i of
      DbInstUnitId ByteString
cid [(ByteString, DbModule)]
insts -> forall u.
IsUnitId u =>
u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit (ByteString -> UnitKey
mkUnitKey' ByteString
cid) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap ByteString -> ModuleName
mkModuleName' DbModule -> GenModule (GenUnit UnitKey)
mkModule') [(ByteString, DbModule)]
insts)
      DbUnitId ByteString
uid           -> forall uid. Definite uid -> GenUnit uid
RealUnit (forall unit. unit -> Definite unit
Definite (ByteString -> UnitKey
mkUnitKey' ByteString
uid))
     mkModule' :: DbModule -> GenModule (GenUnit UnitKey)
mkModule' DbModule
m = case DbModule
m of
       DbModule DbInstUnitId
uid ByteString
n -> forall u. u -> ModuleName -> GenModule u
mkModule (DbInstUnitId -> GenUnit UnitKey
mkVirtUnitKey' DbInstUnitId
uid) (ByteString -> ModuleName
mkModuleName' ByteString
n)
       DbModuleVar  ByteString
n -> forall u. ModuleName -> GenModule (GenUnit u)
mkHoleModule (ByteString -> ModuleName
mkModuleName' ByteString
n)

-- | Map over the unit parameter
mapUnitInfo :: IsUnitId v => (u -> v) -> GenUnitInfo u -> GenUnitInfo v
mapUnitInfo :: forall v u.
IsUnitId v =>
(u -> v) -> GenUnitInfo u -> GenUnitInfo v
mapUnitInfo u -> v
f = forall uid1 uid2 srcpkg1 srcpkg2 srcpkgname1 srcpkgname2 modname1
       modname2 mod1 mod2.
(uid1 -> uid2)
-> (srcpkg1 -> srcpkg2)
-> (srcpkgname1 -> srcpkgname2)
-> (modname1 -> modname2)
-> (mod1 -> mod2)
-> GenericUnitInfo srcpkg1 srcpkgname1 uid1 modname1 mod1
-> GenericUnitInfo srcpkg2 srcpkgname2 uid2 modname2 mod2
mapGenericUnitInfo
   u -> v
f         -- unit identifier
   forall a. a -> a
id        -- package identifier
   forall a. a -> a
id        -- package name
   forall a. a -> a
id        -- module name
   (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall v u. IsUnitId v => (u -> v) -> GenUnit u -> GenUnit v
mapGenUnit u -> v
f)) -- instantiating modules

newtype PackageId   = PackageId    FastString deriving (PackageId -> PackageId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageId -> PackageId -> Bool
$c/= :: PackageId -> PackageId -> Bool
== :: PackageId -> PackageId -> Bool
$c== :: PackageId -> PackageId -> Bool
Eq)
newtype PackageName = PackageName
   { PackageName -> FastString
unPackageName :: FastString
   }
   deriving (PackageName -> PackageName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageName -> PackageName -> Bool
$c/= :: PackageName -> PackageName -> Bool
== :: PackageName -> PackageName -> Bool
$c== :: PackageName -> PackageName -> Bool
Eq)

instance Uniquable PackageId where
  getUnique :: PackageId -> Unique
getUnique (PackageId FastString
n) = forall a. Uniquable a => a -> Unique
getUnique FastString
n

instance Uniquable PackageName where
  getUnique :: PackageName -> Unique
getUnique (PackageName FastString
n) = forall a. Uniquable a => a -> Unique
getUnique FastString
n

instance Outputable PackageId where
  ppr :: PackageId -> SDoc
ppr (PackageId FastString
str) = forall doc. IsLine doc => FastString -> doc
ftext FastString
str

instance Outputable PackageName where
  ppr :: PackageName -> SDoc
ppr (PackageName FastString
str) = forall doc. IsLine doc => FastString -> doc
ftext FastString
str

unitPackageIdString :: GenUnitInfo u -> String
unitPackageIdString :: forall u. GenUnitInfo u -> FilePath
unitPackageIdString GenUnitInfo u
pkg = FastString -> FilePath
unpackFS FastString
str
  where
    PackageId FastString
str = forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> srcpkgid
unitPackageId GenUnitInfo u
pkg

unitPackageNameString :: GenUnitInfo u -> String
unitPackageNameString :: forall u. GenUnitInfo u -> FilePath
unitPackageNameString GenUnitInfo u
pkg = FastString -> FilePath
unpackFS FastString
str
  where
    PackageName FastString
str = forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName GenUnitInfo u
pkg

pprUnitInfo :: UnitInfo -> SDoc
pprUnitInfo :: UnitInfo -> SDoc
pprUnitInfo GenericUnitInfo {Bool
[(ModuleName, Maybe (GenModule (GenUnit UnitId)))]
[(ModuleName, GenModule (GenUnit UnitId))]
[(UnitId, ShortText)]
[ShortText]
[ModuleName]
[UnitId]
Maybe PackageName
Version
ShortText
UnitId
PackageName
PackageId
unitIsTrusted :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Bool
unitIsExposed :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Bool
unitIsIndefinite :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Bool
unitHiddenModules :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [modulename]
unitExposedModules :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitHaddockHTMLs :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitHaddockInterfaces :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludeDirs :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludes :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitCcOptions :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLinkerOptions :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworkDirs :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworks :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDynDirs :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDirs :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepLibsGhc :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepLibsSys :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraries :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitImportDirs :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitAbiDepends :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [(uid, ShortText)]
unitDepends :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> [uid]
unitAbiHash :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> ShortText
unitComponentName :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> Maybe srcpkgname
unitPackageVersion :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version
unitInstantiations :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstanceOf :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> uid
unitId :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> uid
unitIsTrusted :: Bool
unitIsExposed :: Bool
unitIsIndefinite :: Bool
unitHiddenModules :: [ModuleName]
unitExposedModules :: [(ModuleName, Maybe (GenModule (GenUnit UnitId)))]
unitHaddockHTMLs :: [ShortText]
unitHaddockInterfaces :: [ShortText]
unitIncludeDirs :: [ShortText]
unitIncludes :: [ShortText]
unitCcOptions :: [ShortText]
unitLinkerOptions :: [ShortText]
unitExtDepFrameworkDirs :: [ShortText]
unitExtDepFrameworks :: [ShortText]
unitLibraryDynDirs :: [ShortText]
unitLibraryDirs :: [ShortText]
unitExtDepLibsGhc :: [ShortText]
unitExtDepLibsSys :: [ShortText]
unitLibraries :: [ShortText]
unitImportDirs :: [ShortText]
unitAbiDepends :: [(UnitId, ShortText)]
unitDepends :: [UnitId]
unitAbiHash :: ShortText
unitComponentName :: Maybe PackageName
unitPackageVersion :: Version
unitPackageName :: PackageName
unitPackageId :: PackageId
unitInstantiations :: [(ModuleName, GenModule (GenUnit UnitId))]
unitInstanceOf :: UnitId
unitId :: UnitId
unitPackageName :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageId :: forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> srcpkgid
..} =
    forall doc. IsDoc doc => [doc] -> doc
vcat [
      FilePath -> SDoc -> SDoc
field FilePath
"name"                 (forall a. Outputable a => a -> SDoc
ppr PackageName
unitPackageName),
      FilePath -> SDoc -> SDoc
field FilePath
"version"              (forall doc. IsLine doc => FilePath -> doc
text (Version -> FilePath
showVersion Version
unitPackageVersion)),
      FilePath -> SDoc -> SDoc
field FilePath
"id"                   (forall a. Outputable a => a -> SDoc
ppr UnitId
unitId),
      FilePath -> SDoc -> SDoc
field FilePath
"exposed"              (forall a. Outputable a => a -> SDoc
ppr Bool
unitIsExposed),
      FilePath -> SDoc -> SDoc
field FilePath
"exposed-modules"      (forall a. Outputable a => a -> SDoc
ppr [(ModuleName, Maybe (GenModule (GenUnit UnitId)))]
unitExposedModules),
      FilePath -> SDoc -> SDoc
field FilePath
"hidden-modules"       (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [ModuleName]
unitHiddenModules)),
      FilePath -> SDoc -> SDoc
field FilePath
"trusted"              (forall a. Outputable a => a -> SDoc
ppr Bool
unitIsTrusted),
      FilePath -> SDoc -> SDoc
field FilePath
"import-dirs"          (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitImportDirs)),
      FilePath -> SDoc -> SDoc
field FilePath
"library-dirs"         (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLibraryDirs)),
      FilePath -> SDoc -> SDoc
field FilePath
"dynamic-library-dirs" (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLibraryDynDirs)),
      FilePath -> SDoc -> SDoc
field FilePath
"hs-libraries"         (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLibraries)),
      FilePath -> SDoc -> SDoc
field FilePath
"extra-libraries"      (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepLibsSys)),
      FilePath -> SDoc -> SDoc
field FilePath
"extra-ghci-libraries" (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepLibsGhc)),
      FilePath -> SDoc -> SDoc
field FilePath
"include-dirs"         (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitIncludeDirs)),
      FilePath -> SDoc -> SDoc
field FilePath
"includes"             (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitIncludes)),
      FilePath -> SDoc -> SDoc
field FilePath
"depends"              (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr  [UnitId]
unitDepends)),
      FilePath -> SDoc -> SDoc
field FilePath
"cc-options"           (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitCcOptions)),
      FilePath -> SDoc -> SDoc
field FilePath
"ld-options"           (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLinkerOptions)),
      FilePath -> SDoc -> SDoc
field FilePath
"framework-dirs"       (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepFrameworkDirs)),
      FilePath -> SDoc -> SDoc
field FilePath
"frameworks"           (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepFrameworks)),
      FilePath -> SDoc -> SDoc
field FilePath
"haddock-interfaces"   (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitHaddockInterfaces)),
      FilePath -> SDoc -> SDoc
field FilePath
"haddock-html"         (forall doc. IsLine doc => [doc] -> doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (forall doc. IsLine doc => FilePath -> doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitHaddockHTMLs))
    ]
  where
    field :: FilePath -> SDoc -> SDoc
field FilePath
name SDoc
body = forall doc. IsLine doc => FilePath -> doc
text FilePath
name forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => doc
colon forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc -> SDoc
nest Int
4 SDoc
body

-- | Make a `Unit` from a `UnitInfo`
--
-- If the unit is definite, make a `RealUnit` from `unitId` field.
--
-- If the unit is indefinite, make a `VirtUnit` from `unitInstanceOf` and
-- `unitInstantiations` fields. Note that in this case we don't keep track of
-- `unitId`. It can be retrieved later with "improvement", i.e. matching on
-- `unitInstanceOf/unitInstantiations` fields (see Note [About units] in
-- GHC.Unit).
mkUnit :: UnitInfo -> Unit
mkUnit :: UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p
   | forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Bool
unitIsIndefinite UnitInfo
p = forall u.
IsUnitId u =>
u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit (forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> uid
unitInstanceOf UnitInfo
p) (forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstantiations UnitInfo
p)
   | Bool
otherwise          = forall uid. Definite uid -> GenUnit uid
RealUnit (forall unit. unit -> Definite unit
Definite (forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> uid
unitId UnitInfo
p))

-- | Create a UnitPprInfo from a UnitInfo
mkUnitPprInfo :: (u -> FastString) -> GenUnitInfo u -> UnitPprInfo
mkUnitPprInfo :: forall u. (u -> FastString) -> GenUnitInfo u -> UnitPprInfo
mkUnitPprInfo u -> FastString
ufs GenUnitInfo u
i = FastString -> FilePath -> Version -> Maybe FilePath -> UnitPprInfo
UnitPprInfo
   (u -> FastString
ufs (forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> uid
unitId GenUnitInfo u
i))
   (forall u. GenUnitInfo u -> FilePath
unitPackageNameString GenUnitInfo u
i)
   (forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version
unitPackageVersion GenUnitInfo u
i)
   ((FastString -> FilePath
unpackFS forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> FastString
unPackageName) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> Maybe srcpkgname
unitComponentName GenUnitInfo u
i)

-- | Find all the include directories in the given units
collectIncludeDirs :: [UnitInfo] -> [FilePath]
collectIncludeDirs :: [UnitInfo] -> [FilePath]
collectIncludeDirs [UnitInfo]
ps = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> [a]
ordNub (forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Bool
ST.null) (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludeDirs [UnitInfo]
ps))

-- | Find all the C-compiler options in the given units
collectExtraCcOpts :: [UnitInfo] -> [String]
collectExtraCcOpts :: [UnitInfo] -> [FilePath]
collectExtraCcOpts [UnitInfo]
ps = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitCcOptions [UnitInfo]
ps)

-- | Find all the library directories in the given units for the given ways
collectLibraryDirs :: Ways -> [UnitInfo] -> [FilePath]
collectLibraryDirs :: Ways -> [UnitInfo] -> [FilePath]
collectLibraryDirs Ways
ws = forall a. Ord a => [a] -> [a]
ordNub forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter forall (f :: * -> *) a. Foldable f => f a -> Bool
notNull forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Ways -> UnitInfo -> [FilePath]
libraryDirsForWay Ways
ws)

-- | Find all the frameworks in the given units
collectFrameworks :: [UnitInfo] -> [String]
collectFrameworks :: [UnitInfo] -> [FilePath]
collectFrameworks [UnitInfo]
ps = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworks [UnitInfo]
ps)

-- | Find all the package framework paths in these and the preload packages
collectFrameworksDirs :: [UnitInfo] -> [String]
collectFrameworksDirs :: [UnitInfo] -> [FilePath]
collectFrameworksDirs [UnitInfo]
ps = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack (forall a. Ord a => [a] -> [a]
ordNub (forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Bool
ST.null) (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworkDirs [UnitInfo]
ps)))

-- | Either the 'unitLibraryDirs' or 'unitLibraryDynDirs' as appropriate for the way.
libraryDirsForWay :: Ways -> UnitInfo -> [String]
libraryDirsForWay :: Ways -> UnitInfo -> [FilePath]
libraryDirsForWay Ways
ws
  | Ways -> Way -> Bool
hasWay Ways
ws Way
WayDyn = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDynDirs
  | Bool
otherwise        = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDirs

unitHsLibs :: GhcNameVersion -> Ways -> UnitInfo -> [String]
unitHsLibs :: GhcNameVersion -> Ways -> UnitInfo -> [FilePath]
unitHsLibs GhcNameVersion
namever Ways
ways0 UnitInfo
p = forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath
mkDynName forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
addSuffix forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) (forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraries UnitInfo
p)
  where
        ways1 :: Ways
ways1 = Way -> Ways -> Ways
removeWay Way
WayDyn Ways
ways0
        -- the name of a shared library is libHSfoo-ghc<version>.so
        -- we leave out the _dyn, because it is superfluous

        tag :: FilePath
tag     = Ways -> FilePath
waysTag (Ways -> Ways
fullWays Ways
ways1)
        rts_tag :: FilePath
rts_tag = Ways -> FilePath
waysTag Ways
ways1

        mkDynName :: FilePath -> FilePath
mkDynName FilePath
x
         | Bool -> Bool
not (Ways
ways0 Ways -> Way -> Bool
`hasWay` Way
WayDyn) = FilePath
x
         | FilePath
"HS" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
x         = FilePath
x forall a. [a] -> [a] -> [a]
++ GhcNameVersion -> FilePath
dynLibSuffix GhcNameVersion
namever
           -- For non-Haskell libraries, we use the name "Cfoo". The .a
           -- file is libCfoo.a, and the .so is libfoo.so. That way the
           -- linker knows what we mean for the vanilla (-lCfoo) and dyn
           -- (-lfoo) ways. We therefore need to strip the 'C' off here.
         | Just FilePath
x' <- forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix FilePath
"C" FilePath
x = FilePath
x'
         | Bool
otherwise
            = forall a. HasCallStack => FilePath -> a
panic (FilePath
"Don't understand library name " forall a. [a] -> [a] -> [a]
++ FilePath
x)

        -- Add _thr and other rts suffixes to packages named
        -- `rts` or `rts-1.0`. Why both?  Traditionally the rts
        -- package is called `rts` only.  However the tooling
        -- usually expects a package name to have a version.
        -- As such we will gradually move towards the `rts-1.0`
        -- package name, at which point the `rts` package name
        -- will eventually be unused.
        --
        -- This change elevates the need to add custom hooks
        -- and handling specifically for the `rts` package for
        -- example in ghc-cabal.
        addSuffix :: FilePath -> FilePath
addSuffix rts :: FilePath
rts@FilePath
"HSrts"       = FilePath
rts       forall a. [a] -> [a] -> [a]
++ (FilePath -> FilePath
expandTag FilePath
rts_tag)
        addSuffix rts :: FilePath
rts@FilePath
"HSrts-1.0.2" = FilePath
rts       forall a. [a] -> [a] -> [a]
++ (FilePath -> FilePath
expandTag FilePath
rts_tag)
        addSuffix FilePath
other_lib         = FilePath
other_lib forall a. [a] -> [a] -> [a]
++ (FilePath -> FilePath
expandTag FilePath
tag)

        expandTag :: FilePath -> FilePath
expandTag FilePath
t | forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
t = FilePath
""
                    | Bool
otherwise = Char
'_'forall a. a -> [a] -> [a]
:FilePath
t