module PackageSolver
( analyzePackage
, doesGhcVersionSupportPackage
) where
import Distribution.Types.GenericPackageDescription
import Distribution.PackageDescription.Configuration
import Distribution.Types.PackageDescription
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.Library
import Distribution.Types.Executable
import Distribution.Types.ForeignLib
import Distribution.Types.BuildInfo
import Distribution.Types.SetupBuildInfo
import Distribution.Types.TestSuite
import Distribution.Types.Benchmark
import Distribution.Version
import Distribution.Types.Dependency
import Distribution.Types.PackageName
import Distribution.System
import Distribution.Compiler
import Data.Maybe (fromMaybe, maybeToList)
import Control.Arrow (second)
import CompilerConditions
import GhcDatabase
import qualified Data.Set as S
makeCompilerInfo :: Version -> CompilerInfo
makeCompilerInfo v = unknownCompilerInfo (CompilerId GHC v) NoAbiTag
isBase :: Dependency -> Bool
isBase (Dependency packageName _) = unPackageName packageName == "base"
isCabalLib :: Dependency -> Bool
isCabalLib (Dependency packageName _) = unPackageName packageName == "Cabal"
extractConstraints :: (Dependency -> Bool) -> [Dependency] -> VersionRange
extractConstraints predicate deps =
let constraints = depVerRange <$> filter predicate deps
in foldr intersectVersionRanges anyVersion constraints
queryDependency :: VersionRange -> Dependency -> Bool
queryDependency allowedBaseRange dep@(Dependency _ range)
| isBase dep = not . isNoVersion $ intersectVersionRanges range allowedBaseRange
| otherwise = True
configurePackage :: FlagAssignment
-> VersionRange
-> CompilerInfo
-> GenericPackageDescription
-> Maybe PackageDescription
configurePackage flags allowedBaseRange compiler pkgDescr =
let configuredPkg = finalizePD flags
(ComponentRequestedSpec True True)
(queryDependency allowedBaseRange)
buildPlatform
compiler
[]
pkgDescr
in case configuredPkg of
Left _ -> Nothing
Right (pd, _) -> Just pd
constraintsForBase :: PackageDescription -> VersionRange
constraintsForBase pkgDescr =
let setupDependencies = setupDepends <$> maybeToList (setupBuildInfo pkgDescr)
projectDependencies = map targetBuildDepends $ concat
[ libBuildInfo <$> maybeToList (library pkgDescr)
, libBuildInfo <$> subLibraries pkgDescr
, buildInfo <$> executables pkgDescr
, foreignLibBuildInfo <$> foreignLibs pkgDescr
, testBuildInfo <$> testSuites pkgDescr
, benchmarkBuildInfo <$> benchmarks pkgDescr
]
dependencies = setupDependencies ++ projectDependencies
baseConstraints = map (extractConstraints isBase) dependencies
in foldr intersectVersionRanges anyVersion baseConstraints
constraintsForCabalInSetupDepends :: PackageDescription -> VersionRange
constraintsForCabalInSetupDepends pkgDescr =
let setupDependencies = setupDepends <$> maybeToList (setupBuildInfo pkgDescr)
cabalConstraints = map (extractConstraints isCabalLib) setupDependencies
in foldr intersectVersionRanges anyVersion cabalConstraints
findCandidate :: FlagAssignment
-> GenericPackageDescription
-> GhcDatabase
-> (VersionRange, CompilerInfo)
-> S.Set Version
findCandidate flags pkgDescr db (vr, ci) = fromMaybe mempty $ do
configuredPkg <- configurePackage flags vr ci pkgDescr
let baseConstraints = constraintsForBase configuredPkg
let cabalLibConstraints = constraintsForCabalInSetupDepends configuredPkg
let db' = filterBaseVersionIn db baseConstraints
let db'' = filterMinCabalVersionIn db' cabalLibConstraints
return $ ghcVersions db''
analyzePackage :: FlagAssignment
-> GhcDatabase
-> GenericPackageDescription
-> S.Set Version
analyzePackage flags ghcDb pkgDescr = {-# SCC "vabal-core" #-}
let compilers = map (second makeCompilerInfo)
$ genCompilerAssignments ghcDb pkgDescr
in mconcat $ map (findCandidate flags pkgDescr ghcDb) compilers
doesGhcVersionSupportPackage :: FlagAssignment
-> GhcDatabase
-> GenericPackageDescription
-> Version
-> Bool
doesGhcVersionSupportPackage flags ghcDb pkgDescr selectedGhcVersion = fromMaybe False $ do
let ghc = makeCompilerInfo selectedGhcVersion
configuredPkg <- configurePackage flags anyVersion ghc pkgDescr
let suggestedBaseVersionRange = constraintsForBase configuredPkg
suggestedCabalLibVersionRange = constraintsForCabalInSetupDepends configuredPkg
selectedGhcBaseVersion = baseVersionForGhc ghcDb selectedGhcVersion
selectedGhcCabalLibRange = cabalLibRangeForGhc ghcDb selectedGhcVersion
baseVersionIsFine <- (`withinRange` suggestedBaseVersionRange)
<$> selectedGhcBaseVersion
cabalVersionIsFine <- not
. isNoVersion
. intersectVersionRanges suggestedCabalLibVersionRange
<$> selectedGhcCabalLibRange
return $ baseVersionIsFine && cabalVersionIsFine