module Distribution.Simple.LocalBuildInfo (
LocalBuildInfo(..),
externalPackageDeps,
inplacePackageId,
Component(..),
foldComponent,
componentBuildInfo,
allComponentsBy,
ComponentName(..),
ComponentLocalBuildInfo(..),
withComponentsLBI,
withLibLBI,
withExeLBI,
withTestLBI,
module Distribution.Simple.InstallDirs,
absoluteInstallDirs, prefixRelativeInstallDirs,
substPathTemplate
) where
import Distribution.Simple.InstallDirs hiding (absoluteInstallDirs,
prefixRelativeInstallDirs,
substPathTemplate, )
import qualified Distribution.Simple.InstallDirs as InstallDirs
import Distribution.Simple.Program (ProgramConfiguration)
import Distribution.PackageDescription
( PackageDescription(..), withLib, Library(libBuildInfo), withExe
, Executable(exeName, buildInfo), withTest, TestSuite(..)
, BuildInfo(buildable), Benchmark(..) )
import Distribution.Package
( PackageId, Package(..), InstalledPackageId(..) )
import Distribution.Simple.Compiler
( Compiler(..), PackageDBStack, OptimisationLevel )
import Distribution.Simple.PackageIndex
( PackageIndex )
import Distribution.Simple.Utils
( die )
import Distribution.Simple.Setup
( ConfigFlags )
import Distribution.Text
( display )
import Data.List (nub, find)
data LocalBuildInfo = LocalBuildInfo {
configFlags :: ConfigFlags,
extraConfigArgs :: [String],
installDirTemplates :: InstallDirTemplates,
compiler :: Compiler,
buildDir :: FilePath,
scratchDir :: FilePath,
libraryConfig :: Maybe ComponentLocalBuildInfo,
executableConfigs :: [(String, ComponentLocalBuildInfo)],
compBuildOrder :: [ComponentName],
testSuiteConfigs :: [(String, ComponentLocalBuildInfo)],
benchmarkConfigs :: [(String, ComponentLocalBuildInfo)],
installedPkgs :: PackageIndex,
pkgDescrFile :: Maybe FilePath,
localPkgDescr :: PackageDescription,
withPrograms :: ProgramConfiguration,
withPackageDB :: PackageDBStack,
withVanillaLib:: Bool,
withProfLib :: Bool,
withSharedLib :: Bool,
withDynExe :: Bool,
withProfExe :: Bool,
withOptimization :: OptimisationLevel,
withGHCiLib :: Bool,
splitObjs :: Bool,
stripExes :: Bool,
progPrefix :: PathTemplate,
progSuffix :: PathTemplate
} deriving (Read, Show)
externalPackageDeps :: LocalBuildInfo -> [(InstalledPackageId, PackageId)]
externalPackageDeps lbi = filter (not . internal . snd) $ nub $
maybe [] componentPackageDeps (libraryConfig lbi)
++ concatMap (componentPackageDeps . snd) (executableConfigs lbi)
++ concatMap (componentPackageDeps . snd) (testSuiteConfigs lbi)
++ concatMap (componentPackageDeps . snd) (benchmarkConfigs lbi)
where
internal pkgid = pkgid == packageId (localPkgDescr lbi)
inplacePackageId :: PackageId -> InstalledPackageId
inplacePackageId pkgid = InstalledPackageId (display pkgid ++ "-inplace")
data Component = CLib Library
| CExe Executable
| CTest TestSuite
| CBench Benchmark
deriving (Show, Eq, Read)
data ComponentName = CLibName
| CExeName String
| CTestName String
| CBenchName String
deriving (Show, Eq, Read)
data ComponentLocalBuildInfo = ComponentLocalBuildInfo {
componentPackageDeps :: [(InstalledPackageId, PackageId)]
}
deriving (Read, Show)
foldComponent :: (Library -> a)
-> (Executable -> a)
-> (TestSuite -> a)
-> (Benchmark -> a)
-> Component
-> a
foldComponent f _ _ _ (CLib lib) = f lib
foldComponent _ f _ _ (CExe exe) = f exe
foldComponent _ _ f _ (CTest tst) = f tst
foldComponent _ _ _ f (CBench bch) = f bch
componentBuildInfo :: Component -> BuildInfo
componentBuildInfo =
foldComponent libBuildInfo buildInfo testBuildInfo benchmarkBuildInfo
allComponentsBy :: PackageDescription
-> (Component -> a)
-> [a]
allComponentsBy pkg_descr f =
[ f (CLib lib) | Just lib <- [library pkg_descr]
, buildable (libBuildInfo lib) ]
++ [ f (CExe exe) | exe <- executables pkg_descr
, buildable (buildInfo exe) ]
++ [ f (CTest tst) | tst <- testSuites pkg_descr
, buildable (testBuildInfo tst)
, testEnabled tst ]
++ [ f (CBench bm) | bm <- benchmarks pkg_descr
, buildable (benchmarkBuildInfo bm)
, benchmarkEnabled bm ]
withLibLBI :: PackageDescription -> LocalBuildInfo
-> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO ()
withLibLBI pkg_descr lbi f = withLib pkg_descr $ \lib ->
case libraryConfig lbi of
Just clbi -> f lib clbi
Nothing -> die missingLibConf
withExeLBI :: PackageDescription -> LocalBuildInfo
-> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO ()
withExeLBI pkg_descr lbi f = withExe pkg_descr $ \exe ->
case lookup (exeName exe) (executableConfigs lbi) of
Just clbi -> f exe clbi
Nothing -> die (missingExeConf (exeName exe))
withTestLBI :: PackageDescription -> LocalBuildInfo
-> (TestSuite -> ComponentLocalBuildInfo -> IO ()) -> IO ()
withTestLBI pkg_descr lbi f = withTest pkg_descr $ \test ->
case lookup (testName test) (testSuiteConfigs lbi) of
Just clbi -> f test clbi
Nothing -> die (missingTestConf (testName test))
withComponentsLBI :: PackageDescription -> LocalBuildInfo
-> (Component -> ComponentLocalBuildInfo -> IO ())
-> IO ()
withComponentsLBI pkg_descr lbi f = mapM_ compF (compBuildOrder lbi)
where
compF CLibName =
case library pkg_descr of
Nothing -> die missinglib
Just lib -> case libraryConfig lbi of
Nothing -> die missingLibConf
Just clbi -> f (CLib lib) clbi
where
missinglib = "internal error: component list includes a library "
++ "but the package description contains no library"
compF (CExeName name) =
case find (\exe -> exeName exe == name) (executables pkg_descr) of
Nothing -> die missingexe
Just exe -> case lookup name (executableConfigs lbi) of
Nothing -> die (missingExeConf name)
Just clbi -> f (CExe exe) clbi
where
missingexe = "internal error: component list includes an executable "
++ name ++ " but the package contains no such executable."
compF (CTestName name) =
case find (\tst -> testName tst == name) (testSuites pkg_descr) of
Nothing -> die missingtest
Just tst -> case lookup name (testSuiteConfigs lbi) of
Nothing -> die (missingTestConf name)
Just clbi -> f (CTest tst) clbi
where
missingtest = "internal error: component list includes a test suite "
++ name ++ " but the package contains no such test suite."
compF (CBenchName name) =
case find (\bch -> benchmarkName bch == name) (benchmarks pkg_descr) of
Nothing -> die missingbench
Just bch -> case lookup name (benchmarkConfigs lbi) of
Nothing -> die (missingBenchConf name)
Just clbi -> f (CBench bch) clbi
where
missingbench = "internal error: component list includes a benchmark "
++ name ++ " but the package contains no such benchmark."
missingLibConf :: String
missingExeConf, missingTestConf, missingBenchConf :: String -> String
missingLibConf = "internal error: the package contains a library "
++ "but there is no corresponding configuration data"
missingExeConf name = "internal error: the package contains an executable "
++ name ++ " but there is no corresponding configuration data"
missingTestConf name = "internal error: the package contains a test suite "
++ name ++ " but there is no corresponding configuration data"
missingBenchConf name = "internal error: the package contains a benchmark "
++ name ++ " but there is no corresponding configuration data"
absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest
-> InstallDirs FilePath
absoluteInstallDirs pkg lbi copydest =
InstallDirs.absoluteInstallDirs
(packageId pkg)
(compilerId (compiler lbi))
copydest
(installDirTemplates lbi)
prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo
-> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs pkg_descr lbi =
InstallDirs.prefixRelativeInstallDirs
(packageId pkg_descr)
(compilerId (compiler lbi))
(installDirTemplates lbi)
substPathTemplate :: PackageId -> LocalBuildInfo
-> PathTemplate -> FilePath
substPathTemplate pkgid lbi = fromPathTemplate
. ( InstallDirs.substPathTemplate env )
where env = initialPathTemplateEnv
pkgid
(compilerId (compiler lbi))