{-# LANGUAGE CPP, RecordWildCards, FlexibleInstances, MultiParamTypeClasses #-}
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
#include "HsVersions.h"
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)
import qualified Data.Set as Set
type GenUnitInfo unit = GenericUnitInfo (Indefinite unit) PackageId PackageName unit ModuleName (GenModule (GenUnit unit))
type UnitKeyInfo = GenUnitInfo UnitKey
type UnitInfo = GenUnitInfo UnitId
mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo
mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo
mkUnitKeyInfo = forall uid1 uid2 cid1 cid2 srcpkg1 srcpkg2 srcpkgname1 srcpkgname2
modname1 modname2 mod1 mod2.
(uid1 -> uid2)
-> (cid1 -> cid2)
-> (srcpkg1 -> srcpkg2)
-> (srcpkgname1 -> srcpkgname2)
-> (modname1 -> modname2)
-> (mod1 -> mod2)
-> GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1
-> GenericUnitInfo cid2 srcpkg2 srcpkgname2 uid2 modname2 mod2
mapGenericUnitInfo
ByteString -> UnitKey
mkUnitKey'
ByteString -> Indefinite UnitKey
mkIndefUnitKey'
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
mkIndefUnitKey' :: ByteString -> Indefinite UnitKey
mkIndefUnitKey' ByteString
cid = forall unit. unit -> Indefinite unit
Indefinite (ByteString -> UnitKey
mkUnitKey' ByteString
cid)
mkVirtUnitKey' :: DbInstUnitId -> GenUnit UnitKey
mkVirtUnitKey' DbInstUnitId
i = case DbInstUnitId
i of
DbInstUnitId ByteString
cid [(ByteString, DbModule)]
insts -> forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit (ByteString -> Indefinite UnitKey
mkIndefUnitKey' 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)
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 cid1 cid2 srcpkg1 srcpkg2 srcpkgname1 srcpkgname2
modname1 modname2 mod1 mod2.
(uid1 -> uid2)
-> (cid1 -> cid2)
-> (srcpkg1 -> srcpkg2)
-> (srcpkgname1 -> srcpkgname2)
-> (modname1 -> modname2)
-> (mod1 -> mod2)
-> GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1
-> GenericUnitInfo cid2 srcpkg2 srcpkgname2 uid2 modname2 mod2
mapGenericUnitInfo
u -> v
f
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap u -> v
f)
forall a. a -> a
id
forall a. a -> a
id
forall a. a -> a
id
(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))
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) = FastString -> SDoc
ftext FastString
str
instance Outputable PackageName where
ppr :: PackageName -> SDoc
ppr (PackageName FastString
str) = FastString -> SDoc
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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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
Indefinite UnitId
UnitId
PackageId
PackageName
unitAbiDepends :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(uid, ShortText)]
unitAbiHash :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShortText
unitCcOptions :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitComponentName :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Maybe srcpkgname
unitDepends :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitExposedModules :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitExtDepFrameworkDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworks :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepLibsGhc :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepLibsSys :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitHaddockHTMLs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitHaddockInterfaces :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitHiddenModules :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [modulename]
unitId :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitImportDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludeDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludes :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitInstanceOf :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitInstantiations :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitIsExposed :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsIndefinite :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsTrusted :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitLibraries :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDynDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLinkerOptions :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitPackageVersion :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Version
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 :: Indefinite UnitId
unitId :: UnitId
unitPackageName :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageId :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgid
..} =
[SDoc] -> SDoc
vcat [
FilePath -> SDoc -> SDoc
field FilePath
"name" (forall a. Outputable a => a -> SDoc
ppr PackageName
unitPackageName),
FilePath -> SDoc -> SDoc
field FilePath
"version" (FilePath -> SDoc
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" ([SDoc] -> SDoc
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" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitImportDirs)),
FilePath -> SDoc -> SDoc
field FilePath
"library-dirs" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
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" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLibraryDynDirs)),
FilePath -> SDoc -> SDoc
field FilePath
"hs-libraries" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLibraries)),
FilePath -> SDoc -> SDoc
field FilePath
"extra-libraries" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
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" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepLibsGhc)),
FilePath -> SDoc -> SDoc
field FilePath
"include-dirs" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitIncludeDirs)),
FilePath -> SDoc -> SDoc
field FilePath
"includes" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitIncludes)),
FilePath -> SDoc -> SDoc
field FilePath
"depends" ([SDoc] -> SDoc
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" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitCcOptions)),
FilePath -> SDoc -> SDoc
field FilePath
"ld-options" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitLinkerOptions)),
FilePath -> SDoc -> SDoc
field FilePath
"framework-dirs" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepFrameworkDirs)),
FilePath -> SDoc -> SDoc
field FilePath
"frameworks" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitExtDepFrameworks)),
FilePath -> SDoc -> SDoc
field FilePath
"haddock-interfaces" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
ST.unpack) [ShortText]
unitHaddockInterfaces)),
FilePath -> SDoc -> SDoc
field FilePath
"haddock-html" ([SDoc] -> SDoc
fsep (forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SDoc
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 = FilePath -> SDoc
text FilePath
name SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<+> Int -> SDoc -> SDoc
nest Int
4 SDoc
body
mkUnit :: UnitInfo -> Unit
mkUnit :: UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p
| forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsIndefinite UnitInfo
p = forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitInstanceOf UnitInfo
p) (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
p))
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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenUnitInfo u
i))
(forall u. GenUnitInfo u -> FilePath
unitPackageNameString GenUnitInfo u
i)
(forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Maybe srcpkgname
unitComponentName GenUnitInfo u
i)
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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludeDirs [UnitInfo]
ps))
collectExtraCcOpts :: [UnitInfo] -> [String]
[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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitCcOptions [UnitInfo]
ps)
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)
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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworks [UnitInfo]
ps)
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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitExtDepFrameworkDirs [UnitInfo]
ps)))
libraryDirsForWay :: Ways -> UnitInfo -> [String]
libraryDirsForWay :: Ways -> UnitInfo -> [FilePath]
libraryDirsForWay Ways
ws
| Way
WayDyn forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Ways
ws = forall a b. (a -> b) -> [a] -> [b]
map ShortText -> FilePath
ST.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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 compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraries UnitInfo
p)
where
ways1 :: Ways
ways1 = forall a. (a -> Bool) -> Set a -> Set a
Set.filter (forall a. Eq a => a -> a -> Bool
/= Way
WayDyn) Ways
ways0
ways2 :: Ways
ways2 | Way
WayDebug forall a. Ord a => a -> Set a -> Bool
`Set.member` Ways
ways1 Bool -> Bool -> Bool
|| Way
WayProf forall a. Ord a => a -> Set a -> Bool
`Set.member` Ways
ways1
= forall a. (a -> Bool) -> Set a -> Set a
Set.filter (forall a. Eq a => a -> a -> Bool
/= Way
WayTracing) Ways
ways1
| Bool
otherwise
= Ways
ways1
tag :: FilePath
tag = Ways -> FilePath
waysTag (Ways -> Ways
fullWays Ways
ways2)
rts_tag :: FilePath
rts_tag = Ways -> FilePath
waysTag Ways
ways2
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
| Just FilePath
x' <- forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix FilePath
"C" FilePath
x = FilePath
x'
| Bool
otherwise
= forall a. FilePath -> a
panic (FilePath
"Don't understand library name " forall a. [a] -> [a] -> [a]
++ FilePath
x)
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