Constrain core packages

This commit is contained in:
Michael Snoyman 2014-04-17 19:18:36 +03:00
parent cce500244a
commit a9d7c3006a
5 changed files with 22 additions and 9 deletions

View File

@ -11,6 +11,7 @@ import qualified Data.Set as Set
import Distribution.Text (display, simpleParse)
import Stackage.Types
import qualified System.IO.UTF8
import Data.Char (isSpace)
readBuildPlan :: FilePath -> IO BuildPlan
readBuildPlan fp = do
@ -31,7 +32,7 @@ instance AsString BuildPlan where
toString BuildPlan {..} = concat
[ makeSection "tools" bpTools
, makeSection "packages" $ Map.toList bpPackages
, makeSection "core" $ Set.toList bpCore
, makeSection "core" $ Map.toList bpCore
, makeSection "optional-core" $ Map.toList bpOptionalCore
, makeSection "skipped-tests" $ Set.toList bpSkippedTests
]
@ -44,7 +45,7 @@ instance AsString BuildPlan where
let bp = BuildPlan
{ bpTools = tools
, bpPackages = Map.fromList packages
, bpCore = Set.fromList core
, bpCore = Map.fromList core
, bpOptionalCore = Map.fromList optionalCore
, bpSkippedTests = Set.fromList skipped
}
@ -64,6 +65,15 @@ instance AsString PackageName where
toString (PackageName pn) = pn
fromString s = Right (PackageName s, "")
instance AsString (Maybe Version) where
toString Nothing = ""
toString (Just x) = toString x
fromString s
| all isSpace s = return (Nothing, s)
| otherwise = do
(v, s') <- fromString s
return (Just v, s')
instance AsString a => AsString (PackageName, a) where
toString (PackageName pn, s) = concat [pn, " ", toString s]
fromString s = do

View File

@ -1,4 +1,5 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Stackage.InstallInfo
( getInstallInfo
, bpPackageList
@ -54,15 +55,16 @@ getInstallInfo settings = do
allPackages = dropExcluded settings allPackages'
let totalCore
| ignoreUpgradeableCore settings =
Set.fromList $ map PackageName $ words "base containers template-haskell"
Map.fromList $ map (\n -> (PackageName n, Nothing)) $ words "base containers template-haskell"
| otherwise =
extraCore settings `Set.union` Set.map (\(PackageIdentifier p _) -> p) core
Map.fromList (map (\(PackageIdentifier p v) -> (p, Just v)) (Set.toList core))
`Map.union` Map.fromList (map (, Nothing) (Set.toList $ extraCore settings))
putStrLn "Loading package database"
pdb <- loadPackageDB settings coreMap totalCore allPackages
pdb <- loadPackageDB settings coreMap (Map.keysSet totalCore) allPackages
putStrLn "Narrowing package database"
(final, errs) <- narrowPackageDB settings totalCore pdb $ Set.fromList $ Map.toList $ Map.map snd $ allPackages
(final, errs) <- narrowPackageDB settings (Map.keysSet totalCore) pdb $ Set.fromList $ Map.toList $ Map.map snd $ allPackages
putStrLn "Printing build plan to build-plan.log"
System.IO.UTF8.writeFile "build-plan.log" $ unlines $ map showDep $ Map.toList final

View File

@ -22,6 +22,7 @@ createHackageFile ii h = do
selected = Map.fromList . map toStrs . Map.toList $
fmap spiVersion (iiPackages ii)
`Map.union` iiOptionalCore ii
`Map.union` Map.mapMaybe id (iiCore ii)
toStrs (PackageName name, version) = (name, display version)

View File

@ -41,5 +41,5 @@ makeTarballs bp = do
| version == spiVersion spi -> (stable . (e:), extra)
| otherwise -> (stable, extra)
Nothing
| package `Set.member` bpCore bp -> (stable, extra)
| package `Map.member` bpCore bp -> (stable, extra)
| otherwise -> (stable, extra . (e:))

View File

@ -61,7 +61,7 @@ instance Monoid HaskellPlatform where
HaskellPlatform a x `mappend` HaskellPlatform b y = HaskellPlatform (mappend a b) (mappend x y)
data InstallInfo = InstallInfo
{ iiCore :: Set PackageName
{ iiCore :: Map PackageName (Maybe Version)
, iiPackages :: Map PackageName SelectedPackageInfo
, iiOptionalCore :: Map PackageName Version
-- ^ This is intended to hold onto packages which might be automatically
@ -81,7 +81,7 @@ data SelectedPackageInfo = SelectedPackageInfo
data BuildPlan = BuildPlan
{ bpTools :: [String]
, bpPackages :: Map PackageName SelectedPackageInfo
, bpCore :: Set PackageName
, bpCore :: Map PackageName (Maybe Version)
, bpOptionalCore :: Map PackageName Version
-- ^ See 'iiOptionalCore'
, bpSkippedTests :: Set PackageName