module Distribution.Simple.Configure (configure,
writePersistBuildConfig,
getPersistBuildConfig,
checkPersistBuildConfigOutdated,
maybeGetPersistBuildConfig,
localBuildInfoFile,
getInstalledPackages,
configCompiler, configCompilerAux,
ccLdOptionsBuildInfo,
tryGetConfigStateFile,
checkForeignDeps,
)
where
import Distribution.Simple.Compiler
( CompilerFlavor(..), Compiler(compilerId), compilerFlavor, compilerVersion
, showCompilerId, unsupportedLanguages, unsupportedExtensions
, PackageDB(..), PackageDBStack )
import Distribution.Package
( PackageName(PackageName), PackageIdentifier(..), PackageId
, packageName, packageVersion, Package(..)
, Dependency(Dependency), simplifyDependency
, InstalledPackageId(..) )
import Distribution.InstalledPackageInfo as Installed
( InstalledPackageInfo, InstalledPackageInfo_(..)
, emptyInstalledPackageInfo )
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.PackageIndex (PackageIndex)
import Distribution.PackageDescription as PD
( PackageDescription(..), specVersion, GenericPackageDescription(..)
, Library(..), hasLibs, Executable(..), BuildInfo(..), allExtensions
, HookedBuildInfo, updatePackageDescription, allBuildInfo
, FlagName(..), TestSuite(..)
, allComponentsBy, Component(..), compSel )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription, mapTreeData )
import Distribution.PackageDescription.Check
( PackageCheck(..), checkPackage, checkPackageFiles )
import Distribution.Simple.Hpc ( enableCoverage )
import Distribution.Simple.Program
( Program(..), ProgramLocation(..), ConfiguredProgram(..)
, ProgramConfiguration, defaultProgramConfiguration
, configureAllKnownPrograms, knownPrograms, lookupKnownProgram, addKnownProgram
, userSpecifyArgss, userSpecifyPaths
, requireProgram, requireProgramVersion
, pkgConfigProgram, gccProgram, rawSystemProgramStdoutConf )
import Distribution.Simple.Setup
( ConfigFlags(..), CopyDest(..), fromFlag, fromFlagOrDefault, flagToMaybe )
import Distribution.Simple.InstallDirs
( InstallDirs(..), defaultInstallDirs, combineInstallDirs )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), ComponentLocalBuildInfo(..)
, absoluteInstallDirs, prefixRelativeInstallDirs, inplacePackageId )
import Distribution.Simple.BuildPaths
( autogenModulesDir )
import Distribution.Simple.Utils
( die, warn, info, setupMessage, createDirectoryIfMissingVerbose
, intercalate, cabalVersion
, withFileContents, writeFileAtomic
, withTempFile )
import Distribution.System
( OS(..), buildOS, buildPlatform )
import Distribution.Version
( Version(..), anyVersion, orLaterVersion, withinRange, isAnyVersion )
import Distribution.Verbosity
( Verbosity, lessVerbose )
import qualified Distribution.Simple.GHC as GHC
import qualified Distribution.Simple.JHC as JHC
import qualified Distribution.Simple.LHC as LHC
import qualified Distribution.Simple.NHC as NHC
import qualified Distribution.Simple.Hugs as Hugs
import qualified Distribution.Simple.UHC as UHC
import Control.Monad
( when, unless, foldM, filterM, forM )
import Data.List
( nub, partition, isPrefixOf, inits, find )
import Data.Maybe
( isNothing, catMaybes, mapMaybe )
import Data.Monoid
( Monoid(..) )
import Data.Graph
( SCC(..), graphFromEdges, transposeG, vertices, stronglyConnCompR )
import System.Directory
( doesFileExist, getModificationTime, createDirectoryIfMissing, getTemporaryDirectory )
import System.Exit
( ExitCode(..), exitWith )
import System.FilePath
( (</>), isAbsolute )
import qualified System.Info
( compilerName, compilerVersion )
import System.IO
( hPutStrLn, stderr, hClose )
import Distribution.Text
( Text(disp), display, simpleParse )
import Text.PrettyPrint.HughesPJ
( comma, punctuate, render, nest, sep )
import Distribution.Compat.Exception ( catchExit, catchIO )
import Prelude hiding (catch)
tryGetConfigStateFile :: (Read a) => FilePath -> IO (Either String a)
tryGetConfigStateFile filename = do
exists <- doesFileExist :: FilePath -> IO BooldoesFileExist filename :: FilePathfilename
if not :: Bool -> Boolnot exists :: Boolexists
then return :: Monad m => forall a. a -> m areturn (Left :: a -> Either a bLeft missing :: [Char]missing)
else withFileContents :: FilePath -> (String -> IO a) -> IO awithFileContents filename :: FilePathfilename ($) :: (a -> b) -> a -> b$ \str ->
case lines :: String -> [String]lines str :: Stringstr of
[headder, rest] -> case checkHeader :: String -> Maybe StringcheckHeader headder :: Stringheadder of
Just msg -> return :: Monad m => forall a. a -> m areturn (Left :: a -> Either a bLeft msg :: Stringmsg)
Nothing -> case reads :: Read a => ReadS areads rest :: Stringrest of
[(bi,_)] -> return :: Monad m => forall a. a -> m areturn (Right :: b -> Either a bRight bi :: abi)
_ -> return :: Monad m => forall a. a -> m areturn (Left :: a -> Either a bLeft cantParse :: [Char]cantParse)
_ -> return :: Monad m => forall a. a -> m areturn (Left :: a -> Either a bLeft cantParse :: [Char]cantParse)
where
checkHeader :: String -> Maybe String
checkHeader header = case parseHeader ::
String -> Maybe (PackageIdentifier, PackageIdentifier)parseHeader header :: Stringheader of
Just (cabalId, compId)
| cabalId :: PackageIdentifiercabalId
(==) :: Eq a => a -> a -> Bool== currentCabalId :: PackageIdentifiercurrentCabalId -> Nothing :: Maybe aNothing
| otherwise :: Boolotherwise -> Just :: a -> Maybe aJust (badVersion :: Text a => a -> PackageIdentifier -> [Char]badVersion cabalId :: PackageIdentifiercabalId compId :: PackageIdentifiercompId)
Nothing -> Just :: a -> Maybe aJust cantParse :: [Char]cantParse
missing = "Run the 'configure' command first."
cantParse = "Saved package config file seems to be corrupt. "
(++) :: [a] -> [a] -> [a]++ "Try re-running the 'configure' command."
badVersion cabalId compId
= "You need to re-run the 'configure' command. "
(++) :: [a] -> [a] -> [a]++ "The version of Cabal being used has changed (was "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay cabalId :: PackageIdentifiercabalId (++) :: [a] -> [a] -> [a]++ ", now "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay currentCabalId :: PackageIdentifiercurrentCabalId (++) :: [a] -> [a] -> [a]++ ")."
(++) :: [a] -> [a] -> [a]++ badcompiler :: PackageIdentifier -> [Char]badcompiler compId :: PackageIdentifiercompId
badcompiler compId | compId :: PackageIdentifiercompId (==) :: Eq a => a -> a -> Bool== currentCompilerId :: PackageIdentifiercurrentCompilerId = ""
| otherwise :: Boolotherwise
= " Additionally the compiler is different (was "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay compId :: PackageIdentifiercompId (++) :: [a] -> [a] -> [a]++ ", now "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay currentCompilerId :: PackageIdentifiercurrentCompilerId
(++) :: [a] -> [a] -> [a]++ ") which is probably the cause of the problem."
tryGetPersistBuildConfig :: FilePath -> IO (Either String LocalBuildInfo)
tryGetPersistBuildConfig distPref
= tryGetConfigStateFile :: Read a => FilePath -> IO (Either String a)tryGetConfigStateFile (localBuildInfoFile :: FilePath -> FilePathlocalBuildInfoFile distPref :: FilePathdistPref)
getPersistBuildConfig :: FilePath -> IO LocalBuildInfo
getPersistBuildConfig distPref = do
lbi <- tryGetPersistBuildConfig ::
FilePath -> IO (Either String LocalBuildInfo)tryGetPersistBuildConfig distPref :: FilePathdistPref
either :: (a -> c) -> (b -> c) -> Either a b -> ceither die :: String -> IO adie return :: Monad m => forall a. a -> m areturn lbi :: Either String LocalBuildInfolbi
maybeGetPersistBuildConfig :: FilePath -> IO (Maybe LocalBuildInfo)
maybeGetPersistBuildConfig distPref = do
lbi <- tryGetPersistBuildConfig ::
FilePath -> IO (Either String LocalBuildInfo)tryGetPersistBuildConfig distPref :: FilePathdistPref
return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ either :: (a -> c) -> (b -> c) -> Either a b -> ceither (const :: a -> b -> aconst Nothing :: Maybe aNothing) Just :: a -> Maybe aJust lbi :: Either String LocalBuildInfolbi
writePersistBuildConfig :: FilePath -> LocalBuildInfo -> IO ()
writePersistBuildConfig distPref lbi = do
createDirectoryIfMissing :: Bool -> FilePath -> IO ()createDirectoryIfMissing False :: BoolFalse distPref :: FilePathdistPref
writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic (localBuildInfoFile :: FilePath -> FilePathlocalBuildInfoFile distPref :: FilePathdistPref)
(showHeader :: PackageIdentifier -> StringshowHeader pkgid :: PackageIdentifierpkgid (++) :: [a] -> [a] -> [a]++ '\n' (:) :: a -> [a] -> [a]: show :: Show a => a -> Stringshow lbi :: Either String LocalBuildInfolbi)
where
pkgid = packageId :: Package pkg => pkg -> PackageIdentifierpackageId (localPkgDescr :: LocalBuildInfo -> PackageDescriptionlocalPkgDescr lbi :: Either String LocalBuildInfolbi)
showHeader :: PackageIdentifier -> String
showHeader pkgid =
"Saved package config for " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay pkgid :: PackageIdentifierpkgid
(++) :: [a] -> [a] -> [a]++ " written by " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay currentCabalId :: PackageIdentifiercurrentCabalId
(++) :: [a] -> [a] -> [a]++ " using " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay currentCompilerId :: PackageIdentifiercurrentCompilerId
where
currentCabalId :: PackageIdentifier
currentCabalId = PackageIdentifier :: PackageName -> Version -> PackageIdentifierPackageIdentifier (PackageName :: String -> PackageNamePackageName "Cabal") cabalVersion :: VersioncabalVersion
currentCompilerId :: PackageIdentifier
currentCompilerId = PackageIdentifier :: PackageName -> Version -> PackageIdentifierPackageIdentifier (PackageName :: String -> PackageNamePackageName compilerName :: StringSystem.Info.compilerName)
compilerVersion :: VersionSystem.Info.compilerVersion
parseHeader :: String -> Maybe (PackageIdentifier, PackageIdentifier)
parseHeader header = case words :: String -> [String]words header :: Stringheader of
["Saved", "package", "config", "for", pkgid,
"written", "by", cabalid, "using", compilerid]
-> case (simpleParse :: Text a => String -> Maybe asimpleParse pkgid :: PackageIdentifierpkgid :: Maybe PackageIdentifier,
simpleParse :: Text a => String -> Maybe asimpleParse cabalid :: Stringcabalid,
simpleParse :: Text a => String -> Maybe asimpleParse compilerid :: Stringcompilerid) of
(Just _,
Just cabalid',
Just compilerid') -> Just :: a -> Maybe aJust (cabalid' :: PackageIdentifiercabalid', compilerid' :: PackageIdentifiercompilerid')
_ -> Nothing :: Maybe aNothing
_ -> Nothing :: Maybe aNothing
checkPersistBuildConfigOutdated :: FilePath -> FilePath -> IO Bool
checkPersistBuildConfigOutdated distPref pkg_descr_file = do
t0 <- getModificationTime :: FilePath -> IO ClockTimegetModificationTime pkg_descr_file :: FilePathpkg_descr_file
t1 <- getModificationTime :: FilePath -> IO ClockTimegetModificationTime ($) :: (a -> b) -> a -> b$ localBuildInfoFile :: FilePath -> FilePathlocalBuildInfoFile distPref :: FilePathdistPref
return :: Monad m => forall a. a -> m areturn (t0 :: ClockTimet0 (>) :: Ord a => a -> a -> Bool> t1 :: ClockTimet1)
localBuildInfoFile :: FilePath -> FilePath
localBuildInfoFile distPref = distPref :: FilePathdistPref (</>) :: FilePath -> FilePath -> FilePath</> "setup-config"
configure :: (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags -> IO LocalBuildInfo
configure (pkg_descr0, pbi) cfg
= do let distPref = fromFlag :: Flag a -> afromFlag (configDistPref :: ConfigFlags -> Flag FilePathconfigDistPref cfg :: ConfigFlagscfg)
buildDir' = distPref :: FilePathdistPref (</>) :: FilePath -> FilePath -> FilePath</> "build"
verbosity = fromFlag :: Flag a -> afromFlag (configVerbosity :: ConfigFlags -> Flag VerbosityconfigVerbosity cfg :: ConfigFlagscfg)
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()setupMessage verbosity :: Verbosityverbosity "Configuring" (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr0 :: GenericPackageDescriptionpkg_descr0)
createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose (lessVerbose :: Verbosity -> VerbositylessVerbose verbosity :: Verbosityverbosity) True :: BoolTrue distPref :: FilePathdistPref
let programsConfig = userSpecifyArgss :: [(String, [ProgArg])] -> ProgramDb -> ProgramDbuserSpecifyArgss (configProgramArgs :: ConfigFlags -> [(String, [String])]configProgramArgs cfg :: ConfigFlagscfg)
(.) :: (b -> c) -> (a -> b) -> a -> c. userSpecifyPaths :: [(String, FilePath)] -> ProgramDb -> ProgramDbuserSpecifyPaths (configProgramPaths :: ConfigFlags -> [(String, FilePath)]configProgramPaths cfg :: ConfigFlagscfg)
($) :: (a -> b) -> a -> b$ configPrograms :: ConfigFlags -> ProgramConfigurationconfigPrograms cfg :: ConfigFlagscfg
userInstall = fromFlag :: Flag a -> afromFlag (configUserInstall :: ConfigFlags -> Flag BoolconfigUserInstall cfg :: ConfigFlagscfg)
packageDbs = implicitPackageDbStack :: Bool -> Maybe PackageDB -> PackageDBStackimplicitPackageDbStack userInstall :: BooluserInstall
(flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configPackageDB :: ConfigFlags -> Flag PackageDBconfigPackageDB cfg :: ConfigFlagscfg)
(comp, programsConfig') <- configCompiler ::
Maybe CompilerFlavor
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> Verbosity
-> IO (Compiler, ProgramConfiguration)configCompiler
(flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configHcFlavor :: ConfigFlags -> Flag CompilerFlavorconfigHcFlavor cfg :: ConfigFlagscfg)
(flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configHcPath :: ConfigFlags -> Flag FilePathconfigHcPath cfg :: ConfigFlagscfg) (flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configHcPkg :: ConfigFlags -> Flag FilePathconfigHcPkg cfg :: ConfigFlagscfg)
programsConfig :: ProgramDbprogramsConfig (lessVerbose :: Verbosity -> VerbositylessVerbose verbosity :: Verbosityverbosity)
let version = compilerVersion :: Compiler -> VersioncompilerVersion comp :: Compilercomp
flavor = compilerFlavor :: Compiler -> CompilerFlavorcompilerFlavor comp :: Compilercomp
let pid = packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr0 :: GenericPackageDescriptionpkg_descr0
internalPackage = emptyInstalledPackageInfo :: InstalledPackageInfo_ memptyInstalledPackageInfo {
Installed.installedPackageId = InstalledPackageId :: String -> InstalledPackageIdInstalledPackageId ($) :: (a -> b) -> a -> b$ display :: Text a => a -> Stringdisplay ($) :: (a -> b) -> a -> b$ pid :: PackageIdentifierpid,
Installed.sourcePackageId = pid :: PackageIdentifierpid
}
internalPackageSet = fromList :: [InstalledPackageInfo] -> PackageIndexPackageIndex.fromList [internalPackage :: InstalledPackageInfo_ minternalPackage]
installedPackageSet <- getInstalledPackages ::
Verbosity
-> Compiler
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexgetInstalledPackages (lessVerbose :: Verbosity -> VerbositylessVerbose verbosity :: Verbosityverbosity) comp :: Compilercomp
packageDbs :: PackageDBStackpackageDbs programsConfig' :: ProgramConfigurationprogramsConfig'
let
dependencySatisfiable =
not :: Bool -> Boolnot (.) :: (b -> c) -> (a -> b) -> a -> c. null :: [a] -> Boolnull (.) :: (b -> c) -> (a -> b) -> a -> c. lookupDependency ::
PackageIndex -> Dependency -> [(Version, [InstalledPackageInfo])]PackageIndex.lookupDependency pkgs' :: PackageIndexpkgs'
where
pkgs' = insert :: InstalledPackageInfo -> PackageIndex -> PackageIndexPackageIndex.insert internalPackage :: InstalledPackageInfo_ minternalPackage installedPackageSet :: PackageIndexinstalledPackageSet
enableTest t = t :: CondTree ConfVar [Dependency] TestSuitet { testEnabled = fromFlag :: Flag a -> afromFlag (configTests :: ConfigFlags -> Flag BoolconfigTests cfg :: ConfigFlagscfg) }
flaggedTests = map :: (a -> b) -> [a] -> [b]map (\(n, t) -> (n :: Stringn, mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c bmapTreeData enableTest :: TestSuite -> TestSuiteenableTest t :: CondTree ConfVar [Dependency] TestSuitet))
(condTestSuites ::
GenericPackageDescription
-> [(String, CondTree ConfVar [Dependency] TestSuite)]condTestSuites pkg_descr0 :: GenericPackageDescriptionpkg_descr0)
pkg_descr0'' = pkg_descr0 :: GenericPackageDescriptionpkg_descr0 { condTestSuites = flaggedTests :: [(String, CondTree ConfVar [Dependency] TestSuite)]flaggedTests }
(pkg_descr0', flags) <-
case finalizePackageDescription ::
FlagAssignment
-> (Dependency -> Bool)
-> Platform
-> CompilerId
-> [Dependency]
-> GenericPackageDescription
-> Either [Dependency] (PackageDescription, FlagAssignment)finalizePackageDescription
(configConfigurationsFlags :: ConfigFlags -> FlagAssignmentconfigConfigurationsFlags cfg :: ConfigFlagscfg)
dependencySatisfiable :: Dependency -> BooldependencySatisfiable
buildPlatform :: PlatformDistribution.System.buildPlatform
(compilerId :: Compiler -> CompilerIdcompilerId comp :: Compilercomp)
(configConstraints :: ConfigFlags -> [Dependency]configConstraints cfg :: ConfigFlagscfg)
pkg_descr0'' :: GenericPackageDescriptionpkg_descr0''
of Right r -> return :: Monad m => forall a. a -> m areturn r :: (PackageDescription, FlagAssignment)r
Left missing ->
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "At least the following dependencies are missing:\n"
(++) :: [a] -> [a] -> [a]++ (render :: Doc -> Stringrender (.) :: (b -> c) -> (a -> b) -> a -> c. nest :: Int -> Doc -> Docnest 4 (.) :: (b -> c) -> (a -> b) -> a -> c. sep :: [Doc] -> Docsep (.) :: (b -> c) -> (a -> b) -> a -> c. punctuate :: Doc -> [Doc] -> [Doc]punctuate comma :: Doccomma
(.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (disp :: Text a => a -> Docdisp (.) :: (b -> c) -> (a -> b) -> a -> c. simplifyDependency :: Dependency -> DependencysimplifyDependency)
($) :: (a -> b) -> a -> b$ missing :: [Char]missing)
let pkg_descr =
enableCoverage ::
Bool -> String -> PackageDescription -> PackageDescriptionenableCoverage (fromFlag :: Flag a -> afromFlag (configLibCoverage :: ConfigFlags -> Flag BoolconfigLibCoverage cfg :: ConfigFlagscfg)) distPref :: FilePathdistPref
($) :: (a -> b) -> a -> b$ addExtraIncludeLibDirs :: PackageDescription -> PackageDescriptionaddExtraIncludeLibDirs pkg_descr0' :: PackageDescriptionpkg_descr0'
when :: Monad m => Bool -> m () -> m ()when (not :: Bool -> Boolnot (null :: [a] -> Boolnull flags :: FlagAssignmentflags)) ($) :: (a -> b) -> a -> b$
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Flags chosen: "
(++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate ", " [ name :: [Char]name (++) :: [a] -> [a] -> [a]++ "=" (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay value :: Boolvalue
| (FlagName name, value) <- flags :: FlagAssignmentflags ]
checkPackageProblems ::
Verbosity
-> GenericPackageDescription
-> PackageDescription
-> IO ()checkPackageProblems verbosity :: Verbosityverbosity pkg_descr0 :: GenericPackageDescriptionpkg_descr0
(updatePackageDescription ::
HookedBuildInfo -> PackageDescription -> PackageDescriptionupdatePackageDescription pbi :: HookedBuildInfopbi pkg_descr :: PackageDescriptionpkg_descr)
let selectDependencies =
(\xs -> ([ x :: ResolvedDependencyx | Left x <- xs :: [Either FailedDependency ResolvedDependency]xs ], [ x :: ResolvedDependencyx | Right x <- xs :: [Either FailedDependency ResolvedDependency]xs ]))
(.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (selectDependency ::
PackageIndex
-> PackageIndex
-> Dependency
-> Either FailedDependency ResolvedDependencyselectDependency internalPackageSet :: PackageIndexinternalPackageSet installedPackageSet :: PackageIndexinstalledPackageSet)
(failedDeps, allPkgDeps) = selectDependencies ::
[Dependency] -> ([FailedDependency], [ResolvedDependency])selectDependencies (buildDepends :: PackageDescription -> [Dependency]buildDepends pkg_descr :: PackageDescriptionpkg_descr)
internalPkgDeps = [ pkgid :: PackageIdentifierpkgid | InternalDependency _ pkgid <- allPkgDeps :: [ResolvedDependency]allPkgDeps ]
externalPkgDeps = [ pkg :: InstalledPackageInfopkg | ExternalDependency _ pkg <- allPkgDeps :: [ResolvedDependency]allPkgDeps ]
when :: Monad m => Bool -> m () -> m ()when (not :: Bool -> Boolnot (null :: [a] -> Boolnull internalPkgDeps :: [PackageId]internalPkgDeps) (&&) :: Bool -> Bool -> Bool&& not :: Bool -> Boolnot (newPackageDepsBehaviour :: PackageDescription -> BoolnewPackageDepsBehaviour pkg_descr :: PackageDescriptionpkg_descr)) ($) :: (a -> b) -> a -> b$
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "The field 'build-depends: "
(++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate ", " (map :: (a -> b) -> [a] -> [b]map (display :: Text a => a -> Stringdisplay (.) :: (b -> c) -> (a -> b) -> a -> c. packageName :: Package pkg => pkg -> PackageNamepackageName) internalPkgDeps :: [PackageId]internalPkgDeps)
(++) :: [a] -> [a] -> [a]++ "' refers to a library which is defined within the same "
(++) :: [a] -> [a] -> [a]++ "package. To use this feature the package must specify at "
(++) :: [a] -> [a] -> [a]++ "least 'cabal-version: >= 1.8'."
reportFailedDependencies :: [FailedDependency] -> IO ()reportFailedDependencies failedDeps :: [FailedDependency]failedDeps
reportSelectedDependencies ::
Verbosity -> [ResolvedDependency] -> IO ()reportSelectedDependencies verbosity :: Verbosityverbosity allPkgDeps :: [ResolvedDependency]allPkgDeps
packageDependsIndex <-
case dependencyClosure ::
PackageIndex
-> [InstalledPackageId]
-> Either
PackageIndex [(InstalledPackageInfo, [InstalledPackageId])]PackageIndex.dependencyClosure installedPackageSet :: PackageIndexinstalledPackageSet
(map :: (a -> b) -> [a] -> [b]map installedPackageId :: InstalledPackageInfo_ m -> InstalledPackageIdInstalled.installedPackageId externalPkgDeps :: [InstalledPackageInfo]externalPkgDeps) of
Left packageDependsIndex -> return :: Monad m => forall a. a -> m areturn packageDependsIndex :: PackageIndexpackageDependsIndex
Right broken ->
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "The following installed packages are broken because other"
(++) :: [a] -> [a] -> [a]++ " packages they depend on are missing. These broken "
(++) :: [a] -> [a] -> [a]++ "packages must be rebuilt before they can be used.\n"
(++) :: [a] -> [a] -> [a]++ unlines :: [String] -> Stringunlines [ "package "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg :: InstalledPackageInfopkg)
(++) :: [a] -> [a] -> [a]++ " is broken due to missing package "
(++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate ", " (map :: (a -> b) -> [a] -> [b]map display :: Text a => a -> Stringdisplay deps :: [InstalledPackageId]deps)
| (pkg, deps) <- broken :: [(InstalledPackageInfo, [InstalledPackageId])]broken ]
let pseudoTopPkg = emptyInstalledPackageInfo :: InstalledPackageInfo_ memptyInstalledPackageInfo {
Installed.installedPackageId = InstalledPackageId :: String -> InstalledPackageIdInstalledPackageId (display :: Text a => a -> Stringdisplay (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr :: PackageDescriptionpkg_descr)),
Installed.sourcePackageId = packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr :: PackageDescriptionpkg_descr,
Installed.depends = map :: (a -> b) -> [a] -> [b]map installedPackageId :: InstalledPackageInfo_ m -> InstalledPackageIdInstalled.installedPackageId externalPkgDeps :: [InstalledPackageInfo]externalPkgDeps
}
case dependencyInconsistencies ::
PackageIndex -> [(PackageName, [(PackageId, Version)])]PackageIndex.dependencyInconsistencies
(.) :: (b -> c) -> (a -> b) -> a -> c. insert :: InstalledPackageInfo -> PackageIndex -> PackageIndexPackageIndex.insert pseudoTopPkg :: InstalledPackageInfo_ mpseudoTopPkg
($) :: (a -> b) -> a -> b$ packageDependsIndex :: PackageIndexpackageDependsIndex of
[] -> return :: Monad m => forall a. a -> m areturn ()
inconsistencies ->
warn :: Verbosity -> String -> IO ()warn verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$
"This package indirectly depends on multiple versions of the same "
(++) :: [a] -> [a] -> [a]++ "package. This is highly likely to cause a compile failure.\n"
(++) :: [a] -> [a] -> [a]++ unlines :: [String] -> Stringunlines [ "package " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay pkg :: InstalledPackageInfopkg (++) :: [a] -> [a] -> [a]++ " requires "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (PackageIdentifier :: PackageName -> Version -> PackageIdentifierPackageIdentifier name :: [Char]name ver :: Versionver)
| (name, uses) <- inconsistencies :: [(PackageName, [(PackageId, Version)])]inconsistencies
, (pkg, ver) <- uses :: [(PackageId, Version)]uses ]
defaultDirs <- defaultInstallDirs ::
CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplatesdefaultInstallDirs flavor :: CompilerFlavorflavor userInstall :: BooluserInstall (hasLibs :: PackageDescription -> BoolhasLibs pkg_descr :: PackageDescriptionpkg_descr)
let installDirs = combineInstallDirs ::
(a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs ccombineInstallDirs fromFlagOrDefault :: a -> Flag a -> afromFlagOrDefault
defaultDirs :: InstallDirTemplatesdefaultDirs (configInstallDirs :: ConfigFlags -> InstallDirs (Flag PathTemplate)configInstallDirs cfg :: ConfigFlagscfg)
let langlist = nub :: Eq a => [a] -> [a]nub ($) :: (a -> b) -> a -> b$ catMaybes :: [Maybe a] -> [a]catMaybes ($) :: (a -> b) -> a -> b$ map :: (a -> b) -> [a] -> [b]map defaultLanguage :: BuildInfo -> Maybe LanguagedefaultLanguage (allBuildInfo :: PackageDescription -> [BuildInfo]allBuildInfo pkg_descr :: PackageDescriptionpkg_descr)
let langs = unsupportedLanguages :: Compiler -> [Language] -> [Language]unsupportedLanguages comp :: Compilercomp langlist :: [Language]langlist
when :: Monad m => Bool -> m () -> m ()when (not :: Bool -> Boolnot (null :: [a] -> Boolnull langs :: [Language]langs)) ($) :: (a -> b) -> a -> b$
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "The package " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr0 :: GenericPackageDescriptionpkg_descr0)
(++) :: [a] -> [a] -> [a]++ " requires the following languages which are not "
(++) :: [a] -> [a] -> [a]++ "supported by " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (compilerId :: Compiler -> CompilerIdcompilerId comp :: Compilercomp) (++) :: [a] -> [a] -> [a]++ ": "
(++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate ", " (map :: (a -> b) -> [a] -> [b]map display :: Text a => a -> Stringdisplay langs :: [Language]langs)
let extlist = nub :: Eq a => [a] -> [a]nub ($) :: (a -> b) -> a -> b$ concatMap :: (a -> [b]) -> [a] -> [b]concatMap allExtensions :: BuildInfo -> [Extension]allExtensions (allBuildInfo :: PackageDescription -> [BuildInfo]allBuildInfo pkg_descr :: PackageDescriptionpkg_descr)
let exts = unsupportedExtensions :: Compiler -> [Extension] -> [Extension]unsupportedExtensions comp :: Compilercomp extlist :: [Extension]extlist
when :: Monad m => Bool -> m () -> m ()when (not :: Bool -> Boolnot (null :: [a] -> Boolnull exts :: [Extension]exts)) ($) :: (a -> b) -> a -> b$
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "The package " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr0 :: GenericPackageDescriptionpkg_descr0)
(++) :: [a] -> [a] -> [a]++ " requires the following language extensions which are not "
(++) :: [a] -> [a] -> [a]++ "supported by " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (compilerId :: Compiler -> CompilerIdcompilerId comp :: Compilercomp) (++) :: [a] -> [a] -> [a]++ ": "
(++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate ", " (map :: (a -> b) -> [a] -> [b]map display :: Text a => a -> Stringdisplay exts :: [Extension]exts)
let requiredBuildTools = concatMap :: (a -> [b]) -> [a] -> [b]concatMap buildTools :: BuildInfo -> [Dependency]buildTools (allBuildInfo :: PackageDescription -> [BuildInfo]allBuildInfo pkg_descr :: PackageDescriptionpkg_descr)
let programsConfig'' = foldr :: (a -> b -> b) -> b -> [a] -> bfoldr (addInternalExe :: FilePath -> Executable -> ProgramDb -> ProgramDbaddInternalExe buildDir' :: FilePathbuildDir') programsConfig' :: ProgramConfigurationprogramsConfig'
(executables :: PackageDescription -> [Executable]executables pkg_descr :: PackageDescriptionpkg_descr)
programsConfig''' <-
configureAllKnownPrograms :: Verbosity -> ProgramDb -> IO ProgramDbconfigureAllKnownPrograms (lessVerbose :: Verbosity -> VerbositylessVerbose verbosity :: Verbosityverbosity) programsConfig'' :: ProgramDbprogramsConfig''
(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= configureRequiredPrograms ::
Verbosity
-> [Dependency]
-> ProgramConfiguration
-> IO ProgramConfigurationconfigureRequiredPrograms verbosity :: Verbosityverbosity requiredBuildTools :: [Dependency]requiredBuildTools
(pkg_descr', programsConfig'''') <-
configurePkgconfigPackages ::
Verbosity
-> PackageDescription
-> ProgramConfiguration
-> IO (PackageDescription, ProgramConfiguration)configurePkgconfigPackages verbosity :: Verbosityverbosity pkg_descr :: PackageDescriptionpkg_descr programsConfig''' :: ProgramConfigurationprogramsConfig'''
split_objs <-
if not :: Bool -> Boolnot (fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configSplitObjs :: ConfigFlags -> Flag BoolconfigSplitObjs cfg :: ConfigFlagscfg)
then return :: Monad m => forall a. a -> m areturn False :: BoolFalse
else case flavor :: CompilerFlavorflavor of
GHC | version :: Versionversion (>=) :: Ord a => a -> a -> Bool>= Version :: [Int] -> [String] -> VersionVersion [6,5] [] :: [a][] -> return :: Monad m => forall a. a -> m areturn True :: BoolTrue
_ -> do warn :: Verbosity -> String -> IO ()warn verbosity :: Verbosityverbosity
("this compiler does not support " (++) :: [a] -> [a] -> [a]++
"--enable-split-objs; ignoring")
return :: Monad m => forall a. a -> m areturn False :: BoolFalse
let configLib lib = configComponent :: BuildInfo -> ComponentLocalBuildInfoconfigComponent (libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib)
configExe exe = (exeName :: Executable -> StringexeName exe :: Executableexe, configComponent :: BuildInfo -> ComponentLocalBuildInfoconfigComponent (buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe))
configTest test = (testName :: TestSuite -> StringtestName test :: TestSuitetest,
configComponent :: BuildInfo -> ComponentLocalBuildInfoconfigComponent(testBuildInfo :: TestSuite -> BuildInfotestBuildInfo test :: TestSuitetest))
configComponent bi = ComponentLocalBuildInfo {
componentPackageDeps =
if newPackageDepsBehaviour :: PackageDescription -> BoolnewPackageDepsBehaviour pkg_descr' :: PackageDescriptionpkg_descr'
then [ (installedPackageId :: InstalledPackageInfo_ m -> InstalledPackageIdinstalledPackageId pkg :: InstalledPackageInfopkg, packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg :: InstalledPackageInfopkg)
| pkg <- selectSubset :: Package pkg => BuildInfo -> [pkg] -> [pkg]selectSubset bi :: abi externalPkgDeps :: [InstalledPackageInfo]externalPkgDeps ]
(++) :: [a] -> [a] -> [a]++ [ (inplacePackageId :: PackageId -> InstalledPackageIdinplacePackageId pkgid :: PackageIdentifierpkgid, pkgid :: PackageIdentifierpkgid)
| pkgid <- selectSubset :: Package pkg => BuildInfo -> [pkg] -> [pkg]selectSubset bi :: abi internalPkgDeps :: [PackageId]internalPkgDeps ]
else [ (installedPackageId :: InstalledPackageInfo_ m -> InstalledPackageIdinstalledPackageId pkg :: InstalledPackageInfopkg, packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg :: InstalledPackageInfopkg)
| pkg <- externalPkgDeps :: [InstalledPackageInfo]externalPkgDeps ]
}
selectSubset :: Package pkg => BuildInfo -> [pkg] -> [pkg]
selectSubset bi pkgs =
[ pkg :: InstalledPackageInfopkg | pkg <- pkgs :: [pkg]pkgs, packageName :: Package pkg => pkg -> PackageNamepackageName pkg :: InstalledPackageInfopkg elem :: Eq a => a -> [a] -> Bool`elem` names :: [PackageName]names ]
where
names = [ name :: [Char]name | Dependency name _ <- targetBuildDepends :: BuildInfo -> [Dependency]targetBuildDepends bi :: abi ]
let ipDeps component =
mapMaybe :: (a -> Maybe b) -> [a] -> [b]mapMaybe exeDepToComp :: Dependency -> Maybe ComponentexeDepToComp (buildTools :: BuildInfo -> [Dependency]buildTools bi :: abi)
(++) :: [a] -> [a] -> [a]++ mapMaybe :: (a -> Maybe b) -> [a] -> [b]mapMaybe libDepToComp :: Dependency -> Maybe ComponentlibDepToComp (targetBuildDepends :: BuildInfo -> [Dependency]targetBuildDepends bi :: abi)
where
bi = compSel ::
(Library -> a)
-> (Executable -> a)
-> (TestSuite -> a)
-> Component
-> acompSel libBuildInfo :: Library -> BuildInfolibBuildInfo buildInfo :: Executable -> BuildInfobuildInfo testBuildInfo :: TestSuite -> BuildInfotestBuildInfo ($) :: (a -> b) -> a -> b$ component :: Componentcomponent
exeDepToComp (Dependency (PackageName name) _) =
CExe :: Executable -> ComponentCExe fmap :: Functor f => forall a b. (a -> b) -> f a -> f b`fmap` find :: (a -> Bool) -> [a] -> Maybe afind ((==) :: Eq a => a -> a -> Bool(==) name :: [Char]name (.) :: (b -> c) -> (a -> b) -> a -> c. exeName :: Executable -> StringexeName)
(executables :: PackageDescription -> [Executable]executables pkg_descr' :: PackageDescriptionpkg_descr')
libDepToComp (Dependency pn _)
| pn :: PackageNamepn elem :: Eq a => a -> [a] -> Bool`elem` map :: (a -> b) -> [a] -> [b]map packageName :: Package pkg => pkg -> PackageNamepackageName internalPkgDeps :: [PackageId]internalPkgDeps =
CLib :: Library -> ComponentCLib fmap :: Functor f => forall a b. (a -> b) -> f a -> f b`fmap` library :: PackageDescription -> Maybe Librarylibrary pkg_descr' :: PackageDescriptionpkg_descr'
libDepToComp _ = Nothing :: Maybe aNothing
let sccs = (stronglyConnCompR ::
Ord key => [(node, key, [key])] -> [SCC (node, key, [key])]stronglyConnCompR (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map lkup :: Vertex -> (Component, [Char], [[Char]])lkup (.) :: (b -> c) -> (a -> b) -> a -> c. vertices :: Graph -> [Vertex]vertices (.) :: (b -> c) -> (a -> b) -> a -> c. transposeG :: Graph -> GraphtransposeG) g :: Graphg
where (g, lkup, _) = graphFromEdges ::
Ord key =>
[(node, key, [key])]
-> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex)graphFromEdges
($) :: (a -> b) -> a -> b$ allComponentsBy :: PackageDescription -> (Component -> a) -> [a]allComponentsBy pkg_descr' :: PackageDescriptionpkg_descr'
($) :: (a -> b) -> a -> b$ \c -> (c :: Componentc, key :: Component -> [Char]key c :: Componentc, map :: (a -> b) -> [a] -> [b]map key :: Component -> [Char]key (ipDeps :: Component -> [Component]ipDeps c :: Componentc))
key = compSel ::
(Library -> a)
-> (Executable -> a)
-> (TestSuite -> a)
-> Component
-> acompSel (const :: a -> b -> aconst "library") exeName :: Executable -> StringexeName testName :: TestSuite -> StringtestName
buildOrder <- forM :: Monad m => [a] -> (a -> m b) -> m [b]forM sccs :: [SCC (Component, [Char], [[Char]])]sccs ($) :: (a -> b) -> a -> b$ \scc -> case scc :: SCC (Component, [Char], [[Char]])scc of
AcyclicSCC (c,_,_) -> return :: Monad m => forall a. a -> m areturn c :: Componentc
CyclicSCC vs ->
die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "Found cycle in intrapackage dependency graph:\n "
(++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate " depends on "
(map :: (a -> b) -> [a] -> [b]map (\(_,k,_) -> "'" (++) :: [a] -> [a] -> [a]++ k :: [Char]k (++) :: [a] -> [a] -> [a]++ "'") (vs :: [(Component, [Char], [[Char]])]vs (++) :: [a] -> [a] -> [a]++ [head :: [a] -> ahead vs :: [(Component, [Char], [[Char]])]vs]))
let lbi = LocalBuildInfo {
configFlags = cfg :: ConfigFlagscfg,
extraConfigArgs = [] :: [a][],
installDirTemplates = installDirs :: InstallDirs PathTemplateinstallDirs,
compiler = comp :: Compilercomp,
buildDir = buildDir' :: FilePathbuildDir',
scratchDir = fromFlagOrDefault :: a -> Flag a -> afromFlagOrDefault
(distPref :: FilePathdistPref (</>) :: FilePath -> FilePath -> FilePath</> "scratch")
(configScratchDir :: ConfigFlags -> Flag FilePathconfigScratchDir cfg :: ConfigFlagscfg),
libraryConfig = configLib :: Library -> ComponentLocalBuildInfoconfigLib fmap :: Functor f => forall a b. (a -> b) -> f a -> f b`fmap` library :: PackageDescription -> Maybe Librarylibrary pkg_descr' :: PackageDescriptionpkg_descr',
executableConfigs = configExe :: Executable -> (String, ComponentLocalBuildInfo)configExe fmap :: Functor f => forall a b. (a -> b) -> f a -> f b`fmap` executables :: PackageDescription -> [Executable]executables pkg_descr' :: PackageDescriptionpkg_descr',
testSuiteConfigs = configTest :: TestSuite -> (String, ComponentLocalBuildInfo)configTest fmap :: Functor f => forall a b. (a -> b) -> f a -> f b`fmap` testSuites :: PackageDescription -> [TestSuite]testSuites pkg_descr' :: PackageDescriptionpkg_descr',
compBuildOrder = buildOrder :: [Component]buildOrder,
installedPkgs = packageDependsIndex :: PackageIndexpackageDependsIndex,
pkgDescrFile = Nothing :: Maybe aNothing,
localPkgDescr = pkg_descr' :: PackageDescriptionpkg_descr',
withPrograms = programsConfig'''' :: ProgramConfigurationprogramsConfig'''',
withVanillaLib = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configVanillaLib :: ConfigFlags -> Flag BoolconfigVanillaLib cfg :: ConfigFlagscfg,
withProfLib = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configProfLib :: ConfigFlags -> Flag BoolconfigProfLib cfg :: ConfigFlagscfg,
withSharedLib = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configSharedLib :: ConfigFlags -> Flag BoolconfigSharedLib cfg :: ConfigFlagscfg,
withDynExe = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configDynExe :: ConfigFlags -> Flag BoolconfigDynExe cfg :: ConfigFlagscfg,
withProfExe = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configProfExe :: ConfigFlags -> Flag BoolconfigProfExe cfg :: ConfigFlagscfg,
withOptimization = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configOptimization :: ConfigFlags -> Flag OptimisationLevelconfigOptimization cfg :: ConfigFlagscfg,
withGHCiLib = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configGHCiLib :: ConfigFlags -> Flag BoolconfigGHCiLib cfg :: ConfigFlagscfg,
splitObjs = split_objs :: Boolsplit_objs,
stripExes = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configStripExes :: ConfigFlags -> Flag BoolconfigStripExes cfg :: ConfigFlagscfg,
withPackageDB = packageDbs :: PackageDBStackpackageDbs,
progPrefix = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configProgPrefix :: ConfigFlags -> Flag PathTemplateconfigProgPrefix cfg :: ConfigFlagscfg,
progSuffix = fromFlag :: Flag a -> afromFlag ($) :: (a -> b) -> a -> b$ configProgSuffix :: ConfigFlags -> Flag PathTemplateconfigProgSuffix cfg :: ConfigFlagscfg
}
let dirs = absoluteInstallDirs ::
PackageDescription
-> LocalBuildInfo
-> CopyDest
-> InstallDirs FilePathabsoluteInstallDirs pkg_descr :: PackageDescriptionpkg_descr lbi :: Either String LocalBuildInfolbi NoCopyDest :: CopyDestNoCopyDest
relative = prefixRelativeInstallDirs ::
PackageId -> LocalBuildInfo -> InstallDirs (Maybe FilePath)prefixRelativeInstallDirs (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg_descr :: PackageDescriptionpkg_descr) lbi :: Either String LocalBuildInfolbi
unless :: Monad m => Bool -> m () -> m ()unless (isAbsolute :: FilePath -> BoolisAbsolute (prefix :: InstallDirs dir -> dirprefix dirs :: InstallDirs FilePathdirs)) ($) :: (a -> b) -> a -> b$ die :: String -> IO adie ($) :: (a -> b) -> a -> b$
"expected an absolute directory name for --prefix: " (++) :: [a] -> [a] -> [a]++ prefix :: InstallDirs dir -> dirprefix dirs :: InstallDirs FilePathdirs
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Using " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay currentCabalId :: PackageIdentifiercurrentCabalId
(++) :: [a] -> [a] -> [a]++ " compiled by " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay currentCompilerId :: PackageIdentifiercurrentCompilerId
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Using compiler: " (++) :: [a] -> [a] -> [a]++ showCompilerId :: Compiler -> StringshowCompilerId comp :: Compilercomp
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Using install prefix: " (++) :: [a] -> [a] -> [a]++ prefix :: InstallDirs dir -> dirprefix dirs :: InstallDirs FilePathdirs
let dirinfo name dir isPrefixRelative =
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ name :: [Char]name (++) :: [a] -> [a] -> [a]++ " installed in: " (++) :: [a] -> [a] -> [a]++ dir :: [Char]dir (++) :: [a] -> [a] -> [a]++ relNote :: [Char]relNote
where relNote = case buildOS :: OSbuildOS of
Windows | not :: Bool -> Boolnot (hasLibs :: PackageDescription -> BoolhasLibs pkg_descr :: PackageDescriptionpkg_descr)
(&&) :: Bool -> Bool -> Bool&& isNothing :: Maybe a -> BoolisNothing isPrefixRelative :: Maybe aisPrefixRelative
-> " (fixed location)"
_ -> ""
dirinfo :: [Char] -> [Char] -> Maybe a -> IO ()dirinfo "Binaries" (bindir :: InstallDirs dir -> dirbindir dirs :: InstallDirs FilePathdirs) (bindir :: InstallDirs dir -> dirbindir relative :: InstallDirs (Maybe FilePath)relative)
dirinfo :: [Char] -> [Char] -> Maybe a -> IO ()dirinfo "Libraries" (libdir :: InstallDirs dir -> dirlibdir dirs :: InstallDirs FilePathdirs) (libdir :: InstallDirs dir -> dirlibdir relative :: InstallDirs (Maybe FilePath)relative)
dirinfo :: [Char] -> [Char] -> Maybe a -> IO ()dirinfo "Private binaries" (libexecdir :: InstallDirs dir -> dirlibexecdir dirs :: InstallDirs FilePathdirs) (libexecdir :: InstallDirs dir -> dirlibexecdir relative :: InstallDirs (Maybe FilePath)relative)
dirinfo :: [Char] -> [Char] -> Maybe a -> IO ()dirinfo "Data files" (datadir :: InstallDirs dir -> dirdatadir dirs :: InstallDirs FilePathdirs) (datadir :: InstallDirs dir -> dirdatadir relative :: InstallDirs (Maybe FilePath)relative)
dirinfo :: [Char] -> [Char] -> Maybe a -> IO ()dirinfo "Documentation" (docdir :: InstallDirs dir -> dirdocdir dirs :: InstallDirs FilePathdirs) (docdir :: InstallDirs dir -> dirdocdir relative :: InstallDirs (Maybe FilePath)relative)
sequence_ :: Monad m => [m a] -> m ()sequence_ [ reportProgram ::
Verbosity -> Program -> Maybe ConfiguredProgram -> IO ()reportProgram verbosity :: Verbosityverbosity prog :: Programprog configuredProg :: Maybe ConfiguredProgramconfiguredProg
| (prog, configuredProg) <- knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)]knownPrograms programsConfig'''' :: ProgramConfigurationprogramsConfig'''' ]
return :: Monad m => forall a. a -> m areturn lbi :: Either String LocalBuildInfolbi
where
addInternalExe bd exe =
let nm = exeName :: Executable -> StringexeName exe :: Executableexe in
addKnownProgram :: Program -> ProgramDb -> ProgramDbaddKnownProgram Program {
programName = nm :: Stringnm,
programFindLocation = \_ -> return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ Just :: a -> Maybe aJust ($) :: (a -> b) -> a -> b$ bd :: FilePathbd (</>) :: FilePath -> FilePath -> FilePath</> nm :: Stringnm (</>) :: FilePath -> FilePath -> FilePath</> nm :: Stringnm,
programFindVersion = \_ _ -> return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing,
programPostConf = \_ _ -> return :: Monad m => forall a. a -> m areturn [] :: [a][]
}
addExtraIncludeLibDirs pkg_descr =
let extraBi = mempty :: Monoid a => amempty { extraLibDirs = configExtraLibDirs :: ConfigFlags -> [FilePath]configExtraLibDirs cfg :: ConfigFlagscfg
, PD.includeDirs = configExtraIncludeDirs :: ConfigFlags -> [FilePath]configExtraIncludeDirs cfg :: ConfigFlagscfg}
modifyLib l = l :: Libraryl{ libBuildInfo = libBuildInfo :: Library -> BuildInfolibBuildInfo l :: Libraryl mappend :: Monoid a => a -> a -> a`mappend` extraBi :: BuildInfoextraBi }
modifyExecutable e = e :: Executablee{ buildInfo = buildInfo :: Executable -> BuildInfobuildInfo e :: Executablee mappend :: Monoid a => a -> a -> a`mappend` extraBi :: BuildInfoextraBi}
in pkg_descr :: PackageDescriptionpkg_descr{ library = modifyLib :: Library -> LibrarymodifyLib fmap :: Functor f => forall a b. (a -> b) -> f a -> f b`fmap` library :: PackageDescription -> Maybe Librarylibrary pkg_descr :: PackageDescriptionpkg_descr
, executables = modifyExecutable :: Executable -> ExecutablemodifyExecutable map :: (a -> b) -> [a] -> [b]`map` executables :: PackageDescription -> [Executable]executables pkg_descr :: PackageDescriptionpkg_descr}
reportProgram :: Verbosity -> Program -> Maybe ConfiguredProgram -> IO ()
reportProgram verbosity prog Nothing
= info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "No " (++) :: [a] -> [a] -> [a]++ programName :: Program -> StringprogramName prog :: Programprog (++) :: [a] -> [a] -> [a]++ " found"
reportProgram verbosity prog (Just configuredProg)
= info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Using " (++) :: [a] -> [a] -> [a]++ programName :: Program -> StringprogramName prog :: Programprog (++) :: [a] -> [a] -> [a]++ version :: Versionversion (++) :: [a] -> [a] -> [a]++ location :: [Char]location
where location = case programLocation :: ConfiguredProgram -> ProgramLocationprogramLocation configuredProg :: Maybe ConfiguredProgramconfiguredProg of
FoundOnSystem p -> " found on system at: " (++) :: [a] -> [a] -> [a]++ p :: FilePathp
UserSpecified p -> " given by user at: " (++) :: [a] -> [a] -> [a]++ p :: FilePathp
version = case programVersion :: ConfiguredProgram -> Maybe VersionprogramVersion configuredProg :: Maybe ConfiguredProgramconfiguredProg of
Nothing -> ""
Just v -> " version " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay v :: Versionv
hackageUrl :: String
hackageUrl = "http://hackage.haskell.org/package/"
data ResolvedDependency = ExternalDependency Dependency InstalledPackageInfo
| InternalDependency Dependency PackageId
data FailedDependency = DependencyNotExists PackageName
| DependencyNoVersion Dependency
selectDependency :: PackageIndex
-> PackageIndex
-> Dependency
-> Either FailedDependency ResolvedDependency
selectDependency internalIndex installedIndex
dep@(Dependency pkgname vr) =
case lookupPackageName ::
PackageIndex -> PackageName -> [(Version, [InstalledPackageInfo])]PackageIndex.lookupPackageName internalIndex :: PackageIndexinternalIndex pkgname :: PackageNamepkgname of
[(_,[pkg])] | packageVersion :: Package pkg => pkg -> VersionpackageVersion pkg :: InstalledPackageInfopkg withinRange :: Version -> VersionRange -> Bool`withinRange` vr :: VersionRangevr
-> Right :: b -> Either a bRight ($) :: (a -> b) -> a -> b$ InternalDependency :: Dependency -> PackageId -> ResolvedDependencyInternalDependency dep :: Dependencydep (packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg :: InstalledPackageInfopkg)
_ -> case lookupDependency ::
PackageIndex -> Dependency -> [(Version, [InstalledPackageInfo])]PackageIndex.lookupDependency installedIndex :: PackageIndexinstalledIndex dep :: Dependencydep of
[] -> Left :: a -> Either a bLeft ($) :: (a -> b) -> a -> b$ DependencyNotExists :: PackageName -> FailedDependencyDependencyNotExists pkgname :: PackageNamepkgname
pkgs -> Right :: b -> Either a bRight ($) :: (a -> b) -> a -> b$ ExternalDependency ::
Dependency -> InstalledPackageInfo -> ResolvedDependencyExternalDependency dep :: Dependencydep ($) :: (a -> b) -> a -> b$
case last :: [a] -> alast pkgs :: [pkg]pkgs of
(_ver, instances) -> head :: [a] -> ahead instances :: [InstalledPackageInfo]instances
reportSelectedDependencies :: Verbosity
-> [ResolvedDependency] -> IO ()
reportSelectedDependencies verbosity deps =
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ unlines :: [String] -> Stringunlines
[ "Dependency " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (simplifyDependency :: Dependency -> DependencysimplifyDependency dep :: Dependencydep)
(++) :: [a] -> [a] -> [a]++ ": using " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay pkgid :: PackageIdentifierpkgid
| resolved <- deps :: [InstalledPackageId]deps
, let (dep, pkgid) = case resolved :: ResolvedDependencyresolved of
ExternalDependency dep' pkg' -> (dep' :: Dependencydep', packageId :: Package pkg => pkg -> PackageIdentifierpackageId pkg' :: InstalledPackageInfopkg')
InternalDependency dep' pkgid' -> (dep' :: Dependencydep', pkgid' :: PackageIdpkgid') ]
reportFailedDependencies :: [FailedDependency] -> IO ()
reportFailedDependencies [] = return :: Monad m => forall a. a -> m areturn ()
reportFailedDependencies failed =
die :: String -> IO adie (intercalate :: [a] -> [[a]] -> [a]intercalate "\n\n" (map :: (a -> b) -> [a] -> [b]map reportFailedDependency :: FailedDependency -> [Char]reportFailedDependency failed :: [FailedDependency]failed))
where
reportFailedDependency (DependencyNotExists pkgname) =
"there is no version of " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay pkgname :: PackageNamepkgname (++) :: [a] -> [a] -> [a]++ " installed.\n"
(++) :: [a] -> [a] -> [a]++ "Perhaps you need to download and install it from\n"
(++) :: [a] -> [a] -> [a]++ hackageUrl :: StringhackageUrl (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay pkgname :: PackageNamepkgname (++) :: [a] -> [a] -> [a]++ "?"
reportFailedDependency (DependencyNoVersion dep) =
"cannot satisfy dependency " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay (simplifyDependency :: Dependency -> DependencysimplifyDependency dep :: Dependencydep) (++) :: [a] -> [a] -> [a]++ "\n"
getInstalledPackages :: Verbosity -> Compiler
-> PackageDBStack -> ProgramConfiguration
-> IO PackageIndex
getInstalledPackages verbosity comp packageDBs progconf = do
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity "Reading installed packages..."
case compilerFlavor :: Compiler -> CompilerFlavorcompilerFlavor comp :: Compilercomp of
GHC -> getInstalledPackages ::
Verbosity
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexGHC.getInstalledPackages verbosity :: Verbosityverbosity packageDBs :: PackageDBStackpackageDBs progconf :: ProgramConfigurationprogconf
Hugs->getInstalledPackages ::
Verbosity
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexHugs.getInstalledPackages verbosity :: Verbosityverbosity packageDBs :: PackageDBStackpackageDBs progconf :: ProgramConfigurationprogconf
JHC -> getInstalledPackages ::
Verbosity
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexJHC.getInstalledPackages verbosity :: Verbosityverbosity packageDBs :: PackageDBStackpackageDBs progconf :: ProgramConfigurationprogconf
LHC -> getInstalledPackages ::
Verbosity
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexLHC.getInstalledPackages verbosity :: Verbosityverbosity packageDBs :: PackageDBStackpackageDBs progconf :: ProgramConfigurationprogconf
NHC -> getInstalledPackages ::
Verbosity
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexNHC.getInstalledPackages verbosity :: Verbosityverbosity packageDBs :: PackageDBStackpackageDBs progconf :: ProgramConfigurationprogconf
UHC -> getInstalledPackages ::
Verbosity
-> Compiler
-> PackageDBStack
-> ProgramConfiguration
-> IO PackageIndexUHC.getInstalledPackages verbosity :: Verbosityverbosity comp :: Compilercomp packageDBs :: PackageDBStackpackageDBs progconf :: ProgramConfigurationprogconf
flv -> die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "don't know how to find the installed packages for "
(++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay flv :: CompilerFlavorflv
implicitPackageDbStack :: Bool -> Maybe PackageDB -> PackageDBStack
implicitPackageDbStack userInstall maybePackageDB
| userInstall :: BooluserInstall = GlobalPackageDB :: PackageDBGlobalPackageDB (:) :: a -> [a] -> [a]: UserPackageDB :: PackageDBUserPackageDB (:) :: a -> [a] -> [a]: extra :: [PackageDB]extra
| otherwise :: Boolotherwise = GlobalPackageDB :: PackageDBGlobalPackageDB (:) :: a -> [a] -> [a]: extra :: [PackageDB]extra
where
extra = case maybePackageDB :: Maybe PackageDBmaybePackageDB of
Just (SpecificPackageDB db) -> [SpecificPackageDB :: FilePath -> PackageDBSpecificPackageDB db :: FilePathdb]
_ -> [] :: [a][]
newPackageDepsBehaviourMinVersion :: Version
newPackageDepsBehaviourMinVersion = Version { versionBranch = [1,7,1], versionTags = [] :: [a][] }
newPackageDepsBehaviour :: PackageDescription -> Bool
newPackageDepsBehaviour pkg =
specVersion :: PackageDescription -> VersionspecVersion pkg :: InstalledPackageInfopkg (>=) :: Ord a => a -> a -> Bool>= newPackageDepsBehaviourMinVersion :: VersionnewPackageDepsBehaviourMinVersion
configureRequiredPrograms :: Verbosity -> [Dependency] -> ProgramConfiguration -> IO ProgramConfiguration
configureRequiredPrograms verbosity deps conf =
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m afoldM (configureRequiredProgram ::
Verbosity
-> ProgramConfiguration
-> Dependency
-> IO ProgramConfigurationconfigureRequiredProgram verbosity :: Verbosityverbosity) conf :: ProgramConfigurationconf deps :: [InstalledPackageId]deps
configureRequiredProgram :: Verbosity -> ProgramConfiguration -> Dependency -> IO ProgramConfiguration
configureRequiredProgram verbosity conf (Dependency (PackageName progName) verRange) =
case lookupKnownProgram :: String -> ProgramDb -> Maybe ProgramlookupKnownProgram progName :: StringprogName conf :: ProgramConfigurationconf of
Nothing -> die :: String -> IO adie ("Unknown build tool " (++) :: [a] -> [a] -> [a]++ progName :: StringprogName)
Just prog
| verRange :: VersionRangeverRange (==) :: Eq a => a -> a -> Bool== anyVersion :: VersionRangeanyVersion -> do
(_, conf') <- requireProgram ::
Verbosity
-> Program
-> ProgramDb
-> IO (ConfiguredProgram, ProgramDb)requireProgram verbosity :: Verbosityverbosity prog :: Programprog conf :: ProgramConfigurationconf
return :: Monad m => forall a. a -> m areturn conf' :: ProgramDbconf'
| otherwise :: Boolotherwise -> do
(_, _, conf') <- requireProgramVersion ::
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)requireProgramVersion verbosity :: Verbosityverbosity prog :: Programprog verRange :: VersionRangeverRange conf :: ProgramConfigurationconf
return :: Monad m => forall a. a -> m areturn conf' :: ProgramDbconf'
configurePkgconfigPackages :: Verbosity -> PackageDescription
-> ProgramConfiguration
-> IO (PackageDescription, ProgramConfiguration)
configurePkgconfigPackages verbosity pkg_descr conf
| null :: [a] -> Boolnull allpkgs :: [Dependency]allpkgs = return :: Monad m => forall a. a -> m areturn (pkg_descr :: PackageDescriptionpkg_descr, conf :: ProgramConfigurationconf)
| otherwise :: Boolotherwise = do
(_, _, conf') <- requireProgramVersion ::
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)requireProgramVersion
(lessVerbose :: Verbosity -> VerbositylessVerbose verbosity :: Verbosityverbosity) pkgConfigProgram :: ProgrampkgConfigProgram
(orLaterVersion :: Version -> VersionRangeorLaterVersion ($) :: (a -> b) -> a -> b$ Version :: [Int] -> [String] -> VersionVersion [0,9,0] [] :: [a][]) conf :: ProgramConfigurationconf
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ requirePkg :: Dependency -> IO ()requirePkg allpkgs :: [Dependency]allpkgs
lib' <- updateLibrary :: Maybe Library -> IO (Maybe Library)updateLibrary (library :: PackageDescription -> Maybe Librarylibrary pkg_descr :: PackageDescriptionpkg_descr)
exes' <- mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM updateExecutable :: Executable -> IO ExecutableupdateExecutable (executables :: PackageDescription -> [Executable]executables pkg_descr :: PackageDescriptionpkg_descr)
let pkg_descr' = pkg_descr :: PackageDescriptionpkg_descr { library = lib' :: Maybe Librarylib', executables = exes' :: [Executable]exes' }
return :: Monad m => forall a. a -> m areturn (pkg_descr' :: PackageDescriptionpkg_descr', conf' :: ProgramDbconf')
where
allpkgs = concatMap :: (a -> [b]) -> [a] -> [b]concatMap pkgconfigDepends :: BuildInfo -> [Dependency]pkgconfigDepends (allBuildInfo :: PackageDescription -> [BuildInfo]allBuildInfo pkg_descr :: PackageDescriptionpkg_descr)
pkgconfig = rawSystemProgramStdoutConf ::
Verbosity
-> Program
-> ProgramConfiguration
-> [ProgArg]
-> IO StringrawSystemProgramStdoutConf (lessVerbose :: Verbosity -> VerbositylessVerbose verbosity :: Verbosityverbosity)
pkgConfigProgram :: ProgrampkgConfigProgram conf :: ProgramConfigurationconf
requirePkg dep@(Dependency (PackageName pkg) range) = do
version <- pkgconfig :: [ProgArg] -> IO Stringpkgconfig ["--modversion", pkg :: InstalledPackageInfopkg]
catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` (\_ -> die :: String -> IO adie notFound :: [Char]notFound)
catchExit :: IO a -> (ExitCode -> IO a) -> IO a`catchExit` (\_ -> die :: String -> IO adie notFound :: [Char]notFound)
case simpleParse :: Text a => String -> Maybe asimpleParse version :: Versionversion of
Nothing -> die :: String -> IO adie "parsing output of pkg-config --modversion failed"
Just v | not :: Bool -> Boolnot (withinRange :: Version -> VersionRange -> BoolwithinRange v :: Versionv range :: VersionRangerange) -> die :: String -> IO adie (badVersion :: Text a => a -> PackageIdentifier -> [Char]badVersion v :: Versionv)
| otherwise :: Boolotherwise -> info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity (depSatisfied :: a -> [Char]depSatisfied v :: Versionv)
where
notFound = "The pkg-config package " (++) :: [a] -> [a] -> [a]++ pkg :: InstalledPackageInfopkg (++) :: [a] -> [a] -> [a]++ versionRequirement :: [Char]versionRequirement
(++) :: [a] -> [a] -> [a]++ " is required but it could not be found."
badVersion v = "The pkg-config package " (++) :: [a] -> [a] -> [a]++ pkg :: InstalledPackageInfopkg (++) :: [a] -> [a] -> [a]++ versionRequirement :: [Char]versionRequirement
(++) :: [a] -> [a] -> [a]++ " is required but the version installed on the"
(++) :: [a] -> [a] -> [a]++ " system is version " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay v :: Versionv
depSatisfied v = "Dependency " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay dep :: Dependencydep
(++) :: [a] -> [a] -> [a]++ ": using version " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay v :: Versionv
versionRequirement
| isAnyVersion :: VersionRange -> BoolisAnyVersion range :: VersionRangerange = ""
| otherwise :: Boolotherwise = " version " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay range :: VersionRangerange
updateLibrary Nothing = return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
updateLibrary (Just lib) = do
bi <- pkgconfigBuildInfo :: [Dependency] -> IO BuildInfopkgconfigBuildInfo (pkgconfigDepends :: BuildInfo -> [Dependency]pkgconfigDepends (libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib))
return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ Just :: a -> Maybe aJust lib :: Librarylib { libBuildInfo = libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib mappend :: Monoid a => a -> a -> a`mappend` bi :: abi }
updateExecutable exe = do
bi <- pkgconfigBuildInfo :: [Dependency] -> IO BuildInfopkgconfigBuildInfo (pkgconfigDepends :: BuildInfo -> [Dependency]pkgconfigDepends (buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe))
return :: Monad m => forall a. a -> m areturn exe :: Executableexe { buildInfo = buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe mappend :: Monoid a => a -> a -> a`mappend` bi :: abi }
pkgconfigBuildInfo :: [Dependency] -> IO BuildInfo
pkgconfigBuildInfo [] = return :: Monad m => forall a. a -> m areturn mempty :: Monoid a => amempty
pkgconfigBuildInfo pkgdeps = do
let pkgs = nub :: Eq a => [a] -> [a]nub [ display :: Text a => a -> Stringdisplay pkg :: InstalledPackageInfopkg | Dependency pkg _ <- pkgdeps :: [Dependency]pkgdeps ]
ccflags <- pkgconfig :: [ProgArg] -> IO Stringpkgconfig ("--cflags" (:) :: a -> [a] -> [a]: pkgs :: [pkg]pkgs)
ldflags <- pkgconfig :: [ProgArg] -> IO Stringpkgconfig ("--libs" (:) :: a -> [a] -> [a]: pkgs :: [pkg]pkgs)
return :: Monad m => forall a. a -> m areturn (ccLdOptionsBuildInfo :: [String] -> [String] -> BuildInfoccLdOptionsBuildInfo (words :: String -> [String]words ccflags :: Stringccflags) (words :: String -> [String]words ldflags :: Stringldflags))
ccLdOptionsBuildInfo :: [String] -> [String] -> BuildInfo
ccLdOptionsBuildInfo cflags ldflags =
let (includeDirs', cflags') = partition :: (a -> Bool) -> [a] -> ([a], [a])partition ("-I" isPrefixOf :: Eq a => [a] -> [a] -> Bool`isPrefixOf`) cflags :: [String]cflags
(extraLibs', ldflags') = partition :: (a -> Bool) -> [a] -> ([a], [a])partition ("-l" isPrefixOf :: Eq a => [a] -> [a] -> Bool`isPrefixOf`) ldflags :: Stringldflags
(extraLibDirs', ldflags'') = partition :: (a -> Bool) -> [a] -> ([a], [a])partition ("-L" isPrefixOf :: Eq a => [a] -> [a] -> Bool`isPrefixOf`) ldflags' :: [[Char]]ldflags'
in mempty :: Monoid a => amempty {
PD.includeDirs = map :: (a -> b) -> [a] -> [b]map (drop :: Int -> [a] -> [a]drop 2) includeDirs' :: [[Char]]includeDirs',
PD.extraLibs = map :: (a -> b) -> [a] -> [b]map (drop :: Int -> [a] -> [a]drop 2) extraLibs' :: [[Char]]extraLibs',
PD.extraLibDirs = map :: (a -> b) -> [a] -> [b]map (drop :: Int -> [a] -> [a]drop 2) extraLibDirs' :: [[Char]]extraLibDirs',
PD.ccOptions = cflags' :: [[Char]]cflags',
PD.ldOptions = ldflags'' :: [[Char]]ldflags''
}
configCompilerAux :: ConfigFlags -> IO (Compiler, ProgramConfiguration)
configCompilerAux cfg = configCompiler ::
Maybe CompilerFlavor
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> Verbosity
-> IO (Compiler, ProgramConfiguration)configCompiler (flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configHcFlavor :: ConfigFlags -> Flag CompilerFlavorconfigHcFlavor cfg :: ConfigFlagscfg)
(flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configHcPath :: ConfigFlags -> Flag FilePathconfigHcPath cfg :: ConfigFlagscfg)
(flagToMaybe :: Flag a -> Maybe aflagToMaybe ($) :: (a -> b) -> a -> b$ configHcPkg :: ConfigFlags -> Flag FilePathconfigHcPkg cfg :: ConfigFlagscfg)
programsConfig :: ProgramDbprogramsConfig
(fromFlag :: Flag a -> afromFlag (configVerbosity :: ConfigFlags -> Flag VerbosityconfigVerbosity cfg :: ConfigFlagscfg))
where
programsConfig = userSpecifyArgss :: [(String, [ProgArg])] -> ProgramDb -> ProgramDbuserSpecifyArgss (configProgramArgs :: ConfigFlags -> [(String, [String])]configProgramArgs cfg :: ConfigFlagscfg)
(.) :: (b -> c) -> (a -> b) -> a -> c. userSpecifyPaths :: [(String, FilePath)] -> ProgramDb -> ProgramDbuserSpecifyPaths (configProgramPaths :: ConfigFlags -> [(String, FilePath)]configProgramPaths cfg :: ConfigFlagscfg)
($) :: (a -> b) -> a -> b$ defaultProgramConfiguration :: ProgramConfigurationdefaultProgramConfiguration
configCompiler :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> Verbosity
-> IO (Compiler, ProgramConfiguration)
configCompiler Nothing _ _ _ _ = die :: String -> IO adie "Unknown compiler"
configCompiler (Just hcFlavor) hcPath hcPkg conf verbosity = do
case hcFlavor :: CompilerFlavorhcFlavor of
GHC -> configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)GHC.configure verbosity :: Verbosityverbosity hcPath :: Maybe FilePathhcPath hcPkg :: Maybe FilePathhcPkg conf :: ProgramConfigurationconf
JHC -> configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)JHC.configure verbosity :: Verbosityverbosity hcPath :: Maybe FilePathhcPath hcPkg :: Maybe FilePathhcPkg conf :: ProgramConfigurationconf
LHC -> do (_,ghcConf) <- configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)GHC.configure verbosity :: Verbosityverbosity Nothing :: Maybe aNothing hcPkg :: Maybe FilePathhcPkg conf :: ProgramConfigurationconf
configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)LHC.configure verbosity :: Verbosityverbosity hcPath :: Maybe FilePathhcPath Nothing :: Maybe aNothing ghcConf :: ProgramConfigurationghcConf
Hugs -> configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)Hugs.configure verbosity :: Verbosityverbosity hcPath :: Maybe FilePathhcPath hcPkg :: Maybe FilePathhcPkg conf :: ProgramConfigurationconf
NHC -> configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)NHC.configure verbosity :: Verbosityverbosity hcPath :: Maybe FilePathhcPath hcPkg :: Maybe FilePathhcPkg conf :: ProgramConfigurationconf
UHC -> configure ::
Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramConfiguration
-> IO (Compiler, ProgramConfiguration)UHC.configure verbosity :: Verbosityverbosity hcPath :: Maybe FilePathhcPath hcPkg :: Maybe FilePathhcPkg conf :: ProgramConfigurationconf
_ -> die :: String -> IO adie "Unknown compiler"
checkForeignDeps :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO ()
checkForeignDeps pkg lbi verbosity = do
ifBuildsWith :: [[Char]] -> [ProgArg] -> IO b -> IO b -> IO bifBuildsWith allHeaders :: [FilePath]allHeaders (commonCcArgs :: [String]commonCcArgs (++) :: [a] -> [a] -> [a]++ makeLdArgs :: [[Char]] -> [[Char]]makeLdArgs allLibs :: [String]allLibs)
(return :: Monad m => forall a. a -> m areturn ())
(do missingLibs <- findMissingLibs :: IO [[Char]]findMissingLibs
missingHdr <- findOffendingHdr :: IO (Maybe (Either [Char] [Char]))findOffendingHdr
explainErrors :: Maybe (Either [Char] [Char]) -> [[Char]] -> IO ()explainErrors missingHdr :: Maybe (Either [Char] [Char])missingHdr missingLibs :: [[Char]]missingLibs)
where
allHeaders = collectField :: (BuildInfo -> [b]) -> [b]collectField includes :: BuildInfo -> [FilePath]PD.includes
allLibs = collectField :: (BuildInfo -> [b]) -> [b]collectField extraLibs :: BuildInfo -> [String]PD.extraLibs
ifBuildsWith headers args success failure = do
ok <- builds :: String -> [ProgArg] -> IO Boolbuilds (makeProgram :: [[Char]] -> StringmakeProgram headers :: [[Char]]headers) args :: [ProgArg]args
if ok :: Boolok then success :: IO bsuccess else failure :: IO bfailure
findOffendingHdr =
ifBuildsWith :: [[Char]] -> [ProgArg] -> IO b -> IO b -> IO bifBuildsWith allHeaders :: [FilePath]allHeaders ccArgs :: [[Char]]ccArgs
(return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing)
(go :: [[[Char]]] -> IO (Maybe (Either [Char] [Char]))go (.) :: (b -> c) -> (a -> b) -> a -> c. tail :: [a] -> [a]tail (.) :: (b -> c) -> (a -> b) -> a -> c. inits :: [a] -> [[a]]inits ($) :: (a -> b) -> a -> b$ allHeaders :: [FilePath]allHeaders)
where
go [] = return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
go (hdrs:hdrsInits) =
ifBuildsWith :: [[Char]] -> [ProgArg] -> IO b -> IO b -> IO bifBuildsWith hdrs :: [[Char]]hdrs cppArgs :: [[Char]]cppArgs
(ifBuildsWith :: [[Char]] -> [ProgArg] -> IO b -> IO b -> IO bifBuildsWith hdrs :: [[Char]]hdrs ccArgs :: [[Char]]ccArgs
(go :: [[[Char]]] -> IO (Maybe (Either [Char] [Char]))go hdrsInits :: [[[Char]]]hdrsInits)
(return :: Monad m => forall a. a -> m areturn (.) :: (b -> c) -> (a -> b) -> a -> c. Just :: a -> Maybe aJust (.) :: (b -> c) -> (a -> b) -> a -> c. Right :: b -> Either a bRight (.) :: (b -> c) -> (a -> b) -> a -> c. last :: [a] -> alast ($) :: (a -> b) -> a -> b$ hdrs :: [[Char]]hdrs))
(return :: Monad m => forall a. a -> m areturn (.) :: (b -> c) -> (a -> b) -> a -> c. Just :: a -> Maybe aJust (.) :: (b -> c) -> (a -> b) -> a -> c. Left :: a -> Either a bLeft (.) :: (b -> c) -> (a -> b) -> a -> c. last :: [a] -> alast ($) :: (a -> b) -> a -> b$ hdrs :: [[Char]]hdrs)
cppArgs = "-E"(:) :: a -> [a] -> [a]:commonCppArgs :: [String]commonCppArgs
ccArgs = "-c"(:) :: a -> [a] -> [a]:commonCcArgs :: [String]commonCcArgs
findMissingLibs = ifBuildsWith :: [[Char]] -> [ProgArg] -> IO b -> IO b -> IO bifBuildsWith [] :: [a][] (makeLdArgs :: [[Char]] -> [[Char]]makeLdArgs allLibs :: [String]allLibs)
(return :: Monad m => forall a. a -> m areturn [] :: [a][])
(filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM (fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap not :: Bool -> Boolnot (.) :: (b -> c) -> (a -> b) -> a -> c. libExists :: [Char] -> IO BoollibExists) allLibs :: [String]allLibs)
libExists lib = builds :: String -> [ProgArg] -> IO Boolbuilds (makeProgram :: [[Char]] -> StringmakeProgram [] :: [a][]) (makeLdArgs :: [[Char]] -> [[Char]]makeLdArgs [lib :: Librarylib])
commonCppArgs = hcDefines :: Compiler -> [String]hcDefines (compiler :: LocalBuildInfo -> Compilercompiler lbi :: Either String LocalBuildInfolbi)
(++) :: [a] -> [a] -> [a]++ [ "-I" (++) :: [a] -> [a] -> [a]++ autogenModulesDir :: LocalBuildInfo -> StringautogenModulesDir lbi :: Either String LocalBuildInfolbi ]
(++) :: [a] -> [a] -> [a]++ [ "-I" (++) :: [a] -> [a] -> [a]++ dir :: [Char]dir | dir <- collectField :: (BuildInfo -> [b]) -> [b]collectField includeDirs :: BuildInfo -> [FilePath]PD.includeDirs ]
(++) :: [a] -> [a] -> [a]++ ["-I."]
(++) :: [a] -> [a] -> [a]++ collectField :: (BuildInfo -> [b]) -> [b]collectField cppOptions :: BuildInfo -> [String]PD.cppOptions
(++) :: [a] -> [a] -> [a]++ collectField :: (BuildInfo -> [b]) -> [b]collectField ccOptions :: BuildInfo -> [String]PD.ccOptions
(++) :: [a] -> [a] -> [a]++ [ "-I" (++) :: [a] -> [a] -> [a]++ dir :: [Char]dir
| dep <- deps :: [InstalledPackageId]deps
, dir <- includeDirs :: InstalledPackageInfo_ m -> [FilePath]Installed.includeDirs dep :: Dependencydep ]
(++) :: [a] -> [a] -> [a]++ [ opt :: Stringopt
| dep <- deps :: [InstalledPackageId]deps
, opt <- ccOptions :: InstalledPackageInfo_ m -> [String]Installed.ccOptions dep :: Dependencydep ]
commonCcArgs = commonCppArgs :: [String]commonCppArgs
(++) :: [a] -> [a] -> [a]++ collectField :: (BuildInfo -> [b]) -> [b]collectField ccOptions :: BuildInfo -> [String]PD.ccOptions
(++) :: [a] -> [a] -> [a]++ [ opt :: Stringopt
| dep <- deps :: [InstalledPackageId]deps
, opt <- ccOptions :: InstalledPackageInfo_ m -> [String]Installed.ccOptions dep :: Dependencydep ]
commonLdArgs = [ "-L" (++) :: [a] -> [a] -> [a]++ dir :: [Char]dir | dir <- collectField :: (BuildInfo -> [b]) -> [b]collectField extraLibDirs :: BuildInfo -> [String]PD.extraLibDirs ]
(++) :: [a] -> [a] -> [a]++ collectField :: (BuildInfo -> [b]) -> [b]collectField ldOptions :: BuildInfo -> [String]PD.ldOptions
(++) :: [a] -> [a] -> [a]++ [ "-L" (++) :: [a] -> [a] -> [a]++ dir :: [Char]dir
| dep <- deps :: [InstalledPackageId]deps
, dir <- libraryDirs :: InstalledPackageInfo_ m -> [FilePath]Installed.libraryDirs dep :: Dependencydep ]
makeLdArgs libs = [ "-l"(++) :: [a] -> [a] -> [a]++lib :: Librarylib | lib <- libs :: [[Char]]libs ] (++) :: [a] -> [a] -> [a]++ commonLdArgs :: [[Char]]commonLdArgs
makeProgram hdrs = unlines :: [String] -> Stringunlines ($) :: (a -> b) -> a -> b$
[ "#include \"" (++) :: [a] -> [a] -> [a]++ hdr :: [Char]hdr (++) :: [a] -> [a] -> [a]++ "\"" | hdr <- hdrs :: [[Char]]hdrs ] (++) :: [a] -> [a] -> [a]++
["int main(int argc, char** argv) { return 0; }"]
collectField f = concatMap :: (a -> [b]) -> [a] -> [b]concatMap f :: BuildInfo -> [b]f allBi :: [BuildInfo]allBi
allBi = allBuildInfo :: PackageDescription -> [BuildInfo]allBuildInfo pkg :: InstalledPackageInfopkg
deps = topologicalOrder :: PackageIndex -> [InstalledPackageInfo]PackageIndex.topologicalOrder (installedPkgs :: LocalBuildInfo -> PackageIndexinstalledPkgs lbi :: Either String LocalBuildInfolbi)
builds program args = do
tempDir <- getTemporaryDirectory :: IO FilePathgetTemporaryDirectory
withTempFile ::
FilePath -> String -> (FilePath -> Handle -> IO a) -> IO awithTempFile tempDir :: FilePathtempDir ".c" ($) :: (a -> b) -> a -> b$ \cName cHnd ->
withTempFile ::
FilePath -> String -> (FilePath -> Handle -> IO a) -> IO awithTempFile tempDir :: FilePathtempDir "" ($) :: (a -> b) -> a -> b$ \oNname oHnd -> do
hPutStrLn :: Handle -> String -> IO ()hPutStrLn cHnd :: HandlecHnd program :: Stringprogram
hClose :: Handle -> IO ()hClose cHnd :: HandlecHnd
hClose :: Handle -> IO ()hClose oHnd :: HandleoHnd
_ <- rawSystemProgramStdoutConf ::
Verbosity
-> Program
-> ProgramConfiguration
-> [ProgArg]
-> IO StringrawSystemProgramStdoutConf verbosity :: Verbosityverbosity
gccProgram :: ProgramgccProgram (withPrograms :: LocalBuildInfo -> ProgramConfigurationwithPrograms lbi :: Either String LocalBuildInfolbi) (cName :: FilePathcName(:) :: a -> [a] -> [a]:"-o"(:) :: a -> [a] -> [a]:oNname :: FilePathoNname(:) :: a -> [a] -> [a]:args :: [ProgArg]args)
return :: Monad m => forall a. a -> m areturn True :: BoolTrue
catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` (\_ -> return :: Monad m => forall a. a -> m areturn False :: BoolFalse)
catchExit :: IO a -> (ExitCode -> IO a) -> IO a`catchExit` (\_ -> return :: Monad m => forall a. a -> m areturn False :: BoolFalse)
explainErrors Nothing [] = return :: Monad m => forall a. a -> m areturn ()
explainErrors hdr libs = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ unlines :: [String] -> Stringunlines ($) :: (a -> b) -> a -> b$
[ if plural :: Boolplural
then "Missing dependencies on foreign libraries:"
else "Missing dependency on a foreign library:"
| missing :: [Char]missing ]
(++) :: [a] -> [a] -> [a]++ case hdr :: [Char]hdr of
Just (Left h) -> ["* Missing (or bad) header file: " (++) :: [a] -> [a] -> [a]++ h :: [Char]h ]
_ -> [] :: [a][]
(++) :: [a] -> [a] -> [a]++ case libs :: [[Char]]libs of
[] -> [] :: [a][]
[lib] -> ["* Missing C library: " (++) :: [a] -> [a] -> [a]++ lib :: Librarylib]
_ -> ["* Missing C libraries: " (++) :: [a] -> [a] -> [a]++ intercalate :: [a] -> [[a]] -> [a]intercalate ", " libs :: [[Char]]libs]
(++) :: [a] -> [a] -> [a]++ [if plural :: Boolplural then messagePlural :: [Char]messagePlural else messageSingular :: [Char]messageSingular | missing :: [Char]missing]
(++) :: [a] -> [a] -> [a]++ case hdr :: [Char]hdr of
Just (Left _) -> [ headerCppMessage :: [Char]headerCppMessage ]
Just (Right h) -> [ (if missing :: [Char]missing then "* " else "")
(++) :: [a] -> [a] -> [a]++ "Bad header file: " (++) :: [a] -> [a] -> [a]++ h :: [Char]h
, headerCcMessage :: [Char]headerCcMessage ]
_ -> [] :: [a][]
where
plural = length :: [a] -> Intlength libs :: [[Char]]libs (>=) :: Ord a => a -> a -> Bool>= 2
missing = not :: Bool -> Boolnot (null :: [a] -> Boolnull libs :: [[Char]]libs)
(||) :: Bool -> Bool -> Bool|| case hdr :: [Char]hdr of Just (Left _) -> True :: BoolTrue; _ -> False :: BoolFalse
messageSingular =
"This problem can usually be solved by installing the system "
(++) :: [a] -> [a] -> [a]++ "package that provides this library (you may need the "
(++) :: [a] -> [a] -> [a]++ "\"-dev\" version). If the library is already installed "
(++) :: [a] -> [a] -> [a]++ "but in a non-standard location then you can use the flags "
(++) :: [a] -> [a] -> [a]++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
(++) :: [a] -> [a] -> [a]++ "where it is."
messagePlural =
"This problem can usually be solved by installing the system "
(++) :: [a] -> [a] -> [a]++ "packages that provide these libraries (you may need the "
(++) :: [a] -> [a] -> [a]++ "\"-dev\" versions). If the libraries are already installed "
(++) :: [a] -> [a] -> [a]++ "but in a non-standard location then you can use the flags "
(++) :: [a] -> [a] -> [a]++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
(++) :: [a] -> [a] -> [a]++ "where they are."
headerCppMessage =
"If the header file does exist, it may contain errors that "
(++) :: [a] -> [a] -> [a]++ "are caught by the C compiler at the preprocessing stage. "
(++) :: [a] -> [a] -> [a]++ "In this case you can re-run configure with the verbosity "
(++) :: [a] -> [a] -> [a]++ "flag -v3 to see the error messages."
headerCcMessage =
"The header file contains a compile error. "
(++) :: [a] -> [a] -> [a]++ "You can re-run configure with the verbosity flag "
(++) :: [a] -> [a] -> [a]++ "-v3 to see the error messages from the C compiler."
hcDefines :: Compiler -> [String]
hcDefines comp =
case compilerFlavor :: Compiler -> CompilerFlavorcompilerFlavor comp :: Compilercomp of
GHC -> ["-D__GLASGOW_HASKELL__=" (++) :: [a] -> [a] -> [a]++ versionInt :: Version -> StringversionInt version :: Versionversion]
JHC -> ["-D__JHC__=" (++) :: [a] -> [a] -> [a]++ versionInt :: Version -> StringversionInt version :: Versionversion]
NHC -> ["-D__NHC__=" (++) :: [a] -> [a] -> [a]++ versionInt :: Version -> StringversionInt version :: Versionversion]
Hugs -> ["-D__HUGS__"]
_ -> [] :: [a][]
where
version = compilerVersion :: Compiler -> VersioncompilerVersion comp :: Compilercomp
versionInt :: Version -> String
versionInt (Version { versionBranch = [] }) = "1"
versionInt (Version { versionBranch = [n] }) = show :: Show a => a -> Stringshow n :: Stringn
versionInt (Version { versionBranch = n1:n2:_ })
=
let s1 = show :: Show a => a -> Stringshow n1 :: Intn1
s2 = show :: Show a => a -> Stringshow n2 :: Intn2
middle = case s2 :: Strings2 of
_ : _ : _ -> ""
_ -> "0"
in s1 :: Strings1 (++) :: [a] -> [a] -> [a]++ middle :: [Char]middle (++) :: [a] -> [a] -> [a]++ s2 :: Strings2
checkPackageProblems :: Verbosity
-> GenericPackageDescription
-> PackageDescription
-> IO ()
checkPackageProblems verbosity gpkg pkg = do
ioChecks <- checkPackageFiles ::
PackageDescription -> FilePath -> IO [PackageCheck]checkPackageFiles pkg :: InstalledPackageInfopkg "."
let pureChecks = checkPackage ::
GenericPackageDescription
-> Maybe PackageDescription
-> [PackageCheck]checkPackage gpkg :: GenericPackageDescriptiongpkg (Just :: a -> Maybe aJust pkg :: InstalledPackageInfopkg)
errors = [ e :: Executablee | PackageBuildImpossible e <- pureChecks :: [PackageCheck]pureChecks (++) :: [a] -> [a] -> [a]++ ioChecks :: [PackageCheck]ioChecks ]
warnings = [ w :: Stringw | PackageBuildWarning w <- pureChecks :: [PackageCheck]pureChecks (++) :: [a] -> [a] -> [a]++ ioChecks :: [PackageCheck]ioChecks ]
if null :: [a] -> Boolnull errors :: [String]errors
then mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (warn :: Verbosity -> String -> IO ()warn verbosity :: Verbosityverbosity) warnings :: [String]warnings
else do mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (hPutStrLn :: Handle -> String -> IO ()hPutStrLn stderr :: Handlestderr (.) :: (b -> c) -> (a -> b) -> a -> c. ("Error: " (++) :: [a] -> [a] -> [a]++)) errors :: [String]errors
exitWith :: ExitCode -> IO aexitWith (ExitFailure :: Int -> ExitCodeExitFailure 1)