mirror of
https://github.com/commercialhaskell/stackage.git
synced 2026-01-12 07:18:31 +01:00
Track multiple haskell-platform versions and determine GHC version
This commit is contained in:
parent
a428d0e41b
commit
f90bccf74a
3
.gitmodules
vendored
3
.gitmodules
vendored
@ -1,3 +0,0 @@
|
||||
[submodule "haskell-platform"]
|
||||
path = haskell-platform
|
||||
url = https://github.com/haskell/haskell-platform.git
|
||||
@ -18,10 +18,10 @@ import System.IO (BufferMode (NoBuffering),
|
||||
import System.Process (rawSystem, runProcess,
|
||||
waitForProcess)
|
||||
|
||||
defaultBuildSettings :: BuildSettings
|
||||
defaultBuildSettings = BuildSettings
|
||||
defaultBuildSettings :: GhcMajorVersion -> BuildSettings
|
||||
defaultBuildSettings version = BuildSettings
|
||||
{ sandboxRoot = "sandbox"
|
||||
, expectedFailuresBuild = defaultExpectedFailures
|
||||
, expectedFailuresBuild = defaultExpectedFailures version
|
||||
, extraArgs = const ["-fnetwork23"]
|
||||
, testWorkerThreads = 4
|
||||
, buildDocs = True
|
||||
|
||||
@ -7,23 +7,18 @@ import Data.Set (fromList)
|
||||
import Distribution.Text (simpleParse)
|
||||
import Stackage.Types
|
||||
|
||||
targetCompilerVersion :: Version
|
||||
targetCompilerVersion =
|
||||
case simpleParse "7.4.2" of
|
||||
Nothing -> error "Invalid targetCompilerVersion"
|
||||
Just v -> v
|
||||
|
||||
-- | Packages which are shipped with GHC but are not included in the
|
||||
-- Haskell Platform list of core packages.
|
||||
defaultExtraCore :: Set PackageName
|
||||
defaultExtraCore = fromList $ map PackageName $ words
|
||||
defaultExtraCore :: GhcMajorVersion -> Set PackageName
|
||||
defaultExtraCore _ = fromList $ map PackageName $ words
|
||||
"binary Win32"
|
||||
|
||||
-- | Test suites which are expected to fail for some reason. The test suite
|
||||
-- will still be run and logs kept, but a failure will not indicate an
|
||||
-- error in our package combination.
|
||||
defaultExpectedFailures :: Set PackageName
|
||||
defaultExpectedFailures = fromList $ map PackageName
|
||||
defaultExpectedFailures :: GhcMajorVersion
|
||||
-> Set PackageName
|
||||
defaultExpectedFailures _ = fromList $ map PackageName
|
||||
[ -- Requires an old version of WAI and Warp for tests
|
||||
"HTTP"
|
||||
|
||||
@ -93,8 +88,8 @@ defaultExpectedFailures = fromList $ map PackageName
|
||||
-- | List of packages for our stable Hackage. All dependencies will be
|
||||
-- included as well. Please indicate who will be maintaining the package
|
||||
-- via comments.
|
||||
defaultStablePackages :: Map PackageName (VersionRange, Maintainer)
|
||||
defaultStablePackages = unPackageMap $ execWriter $ do
|
||||
defaultStablePackages :: GhcMajorVersion -> Map PackageName (VersionRange, Maintainer)
|
||||
defaultStablePackages _ = unPackageMap $ execWriter $ do
|
||||
mapM_ (add "michael@snoyman.com") $ words =<<
|
||||
[ "yesod yesod-newsfeed yesod-sitemap yesod-static yesod-test yesod-bin"
|
||||
, "markdown filesystem-conduit mime-mail-ses"
|
||||
|
||||
@ -3,24 +3,21 @@ module Stackage.GhcPkg where
|
||||
import Stackage.Types
|
||||
import System.Process
|
||||
import Distribution.Text (simpleParse)
|
||||
import Distribution.Version (Version (Version))
|
||||
import Data.Char (isSpace)
|
||||
import qualified Data.Set as Set
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Control.Monad (guard)
|
||||
|
||||
getGlobalPackages :: IO (Set PackageIdentifier)
|
||||
getGlobalPackages = do
|
||||
-- Account for a change in command line option name
|
||||
versionOutput <- readProcess "ghc-pkg" ["--version"] ""
|
||||
let arg = fromMaybe "--no-user-package-db" $ do
|
||||
verS:_ <- Just $ reverse $ words versionOutput
|
||||
v76 <- simpleParse "7.6"
|
||||
ver <- simpleParse verS
|
||||
guard $ ver < (v76 :: Version)
|
||||
return "--no-user-package-conf"
|
||||
getGlobalPackages :: GhcMajorVersion -> IO (Set PackageIdentifier)
|
||||
getGlobalPackages version = do
|
||||
output <- readProcess "ghc-pkg" [arg, "list"] ""
|
||||
fmap Set.unions $ mapM parse $ drop 1 $ lines output
|
||||
where
|
||||
-- Account for a change in command line option name
|
||||
arg
|
||||
| version >= GhcMajorVersion 7 6 = "--no-user-package-db"
|
||||
| otherwise = "--no-user-package-conf"
|
||||
parse s =
|
||||
case clean s of
|
||||
"" -> return Set.empty
|
||||
@ -32,3 +29,11 @@ getGlobalPackages = do
|
||||
stripParens x@('(':_:_)
|
||||
| last x == ')' = tail $ init $ x
|
||||
stripParens x = x
|
||||
|
||||
getGhcVersion :: IO GhcMajorVersion
|
||||
getGhcVersion = do
|
||||
versionOutput <- readProcess "ghc-pkg" ["--version"] ""
|
||||
maybe (error $ "Invalid version output: " ++ show versionOutput) return $ do
|
||||
verS:_ <- Just $ reverse $ words versionOutput
|
||||
Version (x:y:_) _ <- simpleParse verS
|
||||
return $ GhcMajorVersion x y
|
||||
|
||||
@ -10,9 +10,25 @@ import Data.Monoid (Monoid (..))
|
||||
import Data.Set (singleton)
|
||||
import Distribution.Text (simpleParse)
|
||||
import Stackage.Types
|
||||
import System.Directory (doesFileExist)
|
||||
import System.FilePath ((</>))
|
||||
|
||||
loadHaskellPlatform :: SelectSettings -> IO HaskellPlatform
|
||||
loadHaskellPlatform = fmap parseHP . readFile . haskellPlatformCabal
|
||||
loadHaskellPlatform :: SelectSettings -> IO (Maybe HaskellPlatform)
|
||||
loadHaskellPlatform ss = do
|
||||
e <- doesFileExist fp
|
||||
if e
|
||||
then fmap (Just . parseHP) $ readFile fp
|
||||
else return Nothing
|
||||
where
|
||||
GhcMajorVersion x y = selectGhcVersion ss
|
||||
|
||||
fp = haskellPlatformDir ss </> (concat
|
||||
[ "haskell-platform-"
|
||||
, show x
|
||||
, "."
|
||||
, show y
|
||||
, ".cabal"
|
||||
])
|
||||
|
||||
data HPLine = HPLPackage PackageIdentifier
|
||||
| HPLBeginCore
|
||||
|
||||
@ -27,21 +27,23 @@ dropExcluded bs m0 =
|
||||
getInstallInfo :: SelectSettings -> IO InstallInfo
|
||||
getInstallInfo settings = do
|
||||
putStrLn "Loading Haskell Platform"
|
||||
hp <- loadHaskellPlatform settings
|
||||
mhp <- loadHaskellPlatform settings
|
||||
|
||||
core <-
|
||||
if useGlobalDatabase settings
|
||||
then do
|
||||
case mhp of
|
||||
Just hp | not (useGlobalDatabase settings) -> return $ hpcore hp
|
||||
_ -> do
|
||||
putStrLn "Loading core packages from global database"
|
||||
getGlobalPackages
|
||||
else return $ hpcore hp
|
||||
getGlobalPackages $ selectGhcVersion settings
|
||||
let coreMap = Map.unions
|
||||
$ map (\(PackageIdentifier k v) -> Map.singleton k v)
|
||||
$ Set.toList core
|
||||
|
||||
let allPackages'
|
||||
| requireHaskellPlatform settings = Map.union (stablePackages settings) $ identsToRanges (hplibs hp)
|
||||
| otherwise = stablePackages settings
|
||||
let allPackages' =
|
||||
case mhp of
|
||||
Just hp | requireHaskellPlatform settings ->
|
||||
Map.union (stablePackages settings) $ identsToRanges (hplibs hp)
|
||||
_ -> stablePackages settings
|
||||
allPackages = dropExcluded settings allPackages'
|
||||
let totalCore = extraCore settings `Set.union` Set.map (\(PackageIdentifier p _) -> p) core
|
||||
|
||||
@ -80,7 +82,10 @@ getInstallInfo settings = do
|
||||
return InstallInfo
|
||||
{ iiCore = totalCore
|
||||
, iiPackages = Map.map biToSPI final
|
||||
, iiOptionalCore = Map.fromList $ map (\(PackageIdentifier p v) -> (p, v)) $ Set.toList $ hplibs hp
|
||||
, iiOptionalCore = maybe
|
||||
Map.empty
|
||||
(Map.fromList . map (\(PackageIdentifier p v) -> (p, v)) . Set.toList . hplibs)
|
||||
mhp
|
||||
, iiPackageDB = pdb
|
||||
}
|
||||
|
||||
|
||||
@ -37,7 +37,7 @@ import Distribution.PackageDescription.Parse (ParseResult (ParseOk),
|
||||
parsePackageDescription)
|
||||
import Distribution.System (buildArch, buildOS)
|
||||
import Distribution.Version (unionVersionRanges,
|
||||
withinRange)
|
||||
withinRange, Version (Version))
|
||||
import Stackage.Config
|
||||
import Stackage.Types
|
||||
import Stackage.Util
|
||||
@ -67,6 +67,10 @@ loadPackageDB settings coreMap core deps = do
|
||||
addEntries db Tar.Done = return db
|
||||
addEntries db (Tar.Next e es) = addEntry db e >>= flip addEntries es
|
||||
|
||||
ghcVersion' =
|
||||
let GhcMajorVersion x y = selectGhcVersion settings
|
||||
in Version [x, y, 2] []
|
||||
|
||||
addEntry :: PackageDB -> Tar.Entry -> IO PackageDB
|
||||
addEntry pdb e =
|
||||
case getPackageVersion e of
|
||||
@ -144,7 +148,7 @@ loadPackageDB settings coreMap core deps = do
|
||||
flag' `Set.notMember` disabledFlags settings &&
|
||||
flag `elem` flags'
|
||||
checkCond' (Var (Impl compiler range)) =
|
||||
compiler == GHC && withinRange targetCompilerVersion range
|
||||
compiler == GHC && withinRange ghcVersion' range
|
||||
checkCond' (Lit b) = b
|
||||
checkCond' (CNot c) = not $ checkCond' c
|
||||
checkCond' (COr c1 c2) = checkCond' c1 || checkCond' c2
|
||||
|
||||
@ -18,12 +18,12 @@ import Stackage.InstallInfo
|
||||
import Stackage.Types
|
||||
import Stackage.Util
|
||||
|
||||
defaultSelectSettings :: SelectSettings
|
||||
defaultSelectSettings = SelectSettings
|
||||
{ extraCore = defaultExtraCore
|
||||
, expectedFailuresSelect = defaultExpectedFailures
|
||||
, stablePackages = defaultStablePackages
|
||||
, haskellPlatformCabal = "haskell-platform/haskell-platform.cabal"
|
||||
defaultSelectSettings :: GhcMajorVersion -> SelectSettings
|
||||
defaultSelectSettings version = SelectSettings
|
||||
{ extraCore = defaultExtraCore version
|
||||
, expectedFailuresSelect = defaultExpectedFailures version
|
||||
, stablePackages = defaultStablePackages version
|
||||
, haskellPlatformDir = "haskell-platform"
|
||||
, requireHaskellPlatform = True
|
||||
, excludedPackages = empty
|
||||
, flags = \coreMap ->
|
||||
@ -42,6 +42,7 @@ defaultSelectSettings = SelectSettings
|
||||
, allowedPackage = const $ Right ()
|
||||
, useGlobalDatabase = False
|
||||
, skippedTests = empty
|
||||
, selectGhcVersion = version
|
||||
}
|
||||
|
||||
select :: SelectSettings -> IO BuildPlan
|
||||
|
||||
@ -91,7 +91,7 @@ newtype Maintainer = Maintainer { unMaintainer :: String }
|
||||
deriving (Show, Eq, Ord, Read)
|
||||
|
||||
data SelectSettings = SelectSettings
|
||||
{ haskellPlatformCabal :: FilePath
|
||||
{ haskellPlatformDir :: FilePath
|
||||
, flags :: Map PackageName Version -> Set String
|
||||
-- ^ Compile flags which should be turned on. Takes a Map providing the
|
||||
-- core packages so that flags can be set appropriately.
|
||||
@ -119,6 +119,7 @@ data SelectSettings = SelectSettings
|
||||
, skippedTests :: Set PackageName
|
||||
-- ^ Do not build or run test suites, usually in order to avoid a
|
||||
-- dependency.
|
||||
, selectGhcVersion :: GhcMajorVersion
|
||||
}
|
||||
|
||||
data BuildStage = BSBuild | BSTest
|
||||
@ -142,3 +143,7 @@ instance Monoid PackageMap where
|
||||
PackageMap $ unionWith go x y
|
||||
where
|
||||
go (r1, m1) (r2, _) = (intersectVersionRanges r1 r2, m1)
|
||||
|
||||
-- | GHC major version. For example, for GHC 7.4.2, this would be 7 4.
|
||||
data GhcMajorVersion = GhcMajorVersion Int Int
|
||||
deriving (Show, Ord, Eq)
|
||||
|
||||
@ -3,6 +3,7 @@ import Data.Set (fromList)
|
||||
import Stackage.Build (build, defaultBuildSettings)
|
||||
import Stackage.BuildPlan (readBuildPlan, writeBuildPlan)
|
||||
import Stackage.CheckPlan (checkPlan)
|
||||
import Stackage.GhcPkg (getGhcVersion)
|
||||
import Stackage.Init (stackageInit)
|
||||
import Stackage.Select (defaultSelectSettings, select)
|
||||
import Stackage.Tarballs (makeTarballs)
|
||||
@ -49,10 +50,10 @@ data BuildArgs = BuildArgs
|
||||
, noDocs :: Bool
|
||||
}
|
||||
|
||||
parseBuildArgs :: [String] -> IO BuildArgs
|
||||
parseBuildArgs =
|
||||
parseBuildArgs :: GhcMajorVersion -> [String] -> IO BuildArgs
|
||||
parseBuildArgs version =
|
||||
loop BuildArgs
|
||||
{ sandbox = sandboxRoot defaultBuildSettings
|
||||
{ sandbox = sandboxRoot $ defaultBuildSettings version
|
||||
, buildPlanSrc = defaultBuildPlan
|
||||
, extraArgs' = id
|
||||
, noDocs = False
|
||||
@ -70,11 +71,12 @@ defaultBuildPlan = "build-plan.txt"
|
||||
|
||||
withBuildSettings :: [String] -> (BuildSettings -> BuildPlan -> IO a) -> IO a
|
||||
withBuildSettings args f = do
|
||||
BuildArgs {..} <- parseBuildArgs args
|
||||
version <- getGhcVersion
|
||||
BuildArgs {..} <- parseBuildArgs version args
|
||||
bp <- readBuildPlan buildPlanSrc
|
||||
let settings = defaultBuildSettings
|
||||
let settings = (defaultBuildSettings version)
|
||||
{ sandboxRoot = sandbox
|
||||
, extraArgs = extraArgs' . extraArgs defaultBuildSettings
|
||||
, extraArgs = extraArgs' . extraArgs (defaultBuildSettings version)
|
||||
, buildDocs = not noDocs
|
||||
}
|
||||
f settings bp
|
||||
@ -86,8 +88,9 @@ main = do
|
||||
["uploads"] -> checkUploads "allowed.txt" "new-allowed.txt"
|
||||
"select":rest -> do
|
||||
SelectArgs {..} <- parseSelectArgs rest
|
||||
ghcVersion <- getGhcVersion
|
||||
bp <- select
|
||||
defaultSelectSettings
|
||||
(defaultSelectSettings ghcVersion)
|
||||
{ excludedPackages = fromList $ map PackageName excluded
|
||||
, requireHaskellPlatform = not noPlatform
|
||||
, allowedPackage =
|
||||
|
||||
Loading…
Reference in New Issue
Block a user