mirror of
https://github.com/commercialhaskell/stackage.git
synced 2026-01-11 23:08:30 +01:00
Stackage.Config
This commit is contained in:
parent
c3a441eb72
commit
4f8f0259ab
48
Stackage/Config.hs
Normal file
48
Stackage/Config.hs
Normal file
@ -0,0 +1,48 @@
|
||||
module Stackage.Config where
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import Stackage.Types
|
||||
import Control.Monad.Trans.Writer (execWriter, tell)
|
||||
import Data.Set (singleton, fromList)
|
||||
import Control.Monad (when, unless)
|
||||
import Distribution.System (OS (..), buildOS)
|
||||
import Distribution.Version (anyVersion)
|
||||
import Distribution.Text (simpleParse)
|
||||
|
||||
-- | Packages which are shipped with GHC but are not included in the
|
||||
-- Haskell Platform list of core packages.
|
||||
extraCore :: Set PackageName
|
||||
extraCore = singleton $ PackageName "binary"
|
||||
|
||||
-- | 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.
|
||||
expectedFailures :: Set PackageName
|
||||
expectedFailures = fromList $ map PackageName
|
||||
[ -- Requires an old version of WAI and Warp for tests
|
||||
"HTTP"
|
||||
-- Requires a special hspec-meta which is not yet available from
|
||||
-- Hackage.
|
||||
, "hspec"
|
||||
]
|
||||
|
||||
-- | List of packages for our stable Hackage. All dependencies will be
|
||||
-- included as well. Please indicate who will be maintaining the package
|
||||
-- via comments.
|
||||
stablePackages :: Map PackageName VersionRange
|
||||
stablePackages = execWriter $ do
|
||||
-- Michael Snoyman michael@snoyman.com
|
||||
addRange "yesod" "< 1.4"
|
||||
add "yesod-newsfeed"
|
||||
add "yesod-sitemap"
|
||||
add "yesod-static"
|
||||
-- A few transient deps not otherwise picked up
|
||||
add "cipher-aes"
|
||||
when (buildOS == Linux) $ add "hinotify"
|
||||
unless (buildOS == Windows) $ add "unix-time"
|
||||
where
|
||||
add = flip addRange "-any"
|
||||
addRange package range =
|
||||
case simpleParse range of
|
||||
Nothing -> error $ "Invalid range " ++ show range ++ " for " ++ package
|
||||
Just range' -> tell $ Map.singleton (PackageName package) range'
|
||||
@ -1,31 +0,0 @@
|
||||
module Stackage.PackageList where
|
||||
|
||||
import Control.Monad (foldM)
|
||||
import Data.Char (isSpace)
|
||||
import qualified Data.Map as Map
|
||||
import Distribution.Text (simpleParse)
|
||||
import Distribution.Version (anyVersion)
|
||||
import Stackage.Types
|
||||
|
||||
loadPackageList :: FilePath -> IO (Map PackageName VersionRange)
|
||||
loadPackageList fp =
|
||||
readFile fp >>= foldM addLine Map.empty . lines
|
||||
where
|
||||
addLine ps l'
|
||||
| null l = return ps
|
||||
| otherwise =
|
||||
case parseVersionRange v' of
|
||||
Nothing -> error $ "Invalid version range: " ++ show (p, v')
|
||||
Just v -> return $ Map.insert (PackageName p) v ps
|
||||
where
|
||||
l = cleanup l'
|
||||
(p, v') = break isSpace l
|
||||
cleanup = dropWhile isSpace . reverse . dropWhile isSpace . reverse . stripComments
|
||||
|
||||
parseVersionRange l
|
||||
| null $ cleanup l = Just anyVersion
|
||||
| otherwise = simpleParse l
|
||||
|
||||
stripComments "" = ""
|
||||
stripComments ('-':'-':_) = ""
|
||||
stripComments (c:cs) = c : stripComments cs
|
||||
@ -6,9 +6,9 @@ import Data.Version (showVersion)
|
||||
import Stackage.HaskellPlatform
|
||||
import Stackage.LoadDatabase
|
||||
import Stackage.NarrowDatabase
|
||||
import Stackage.PackageList
|
||||
import Stackage.Types
|
||||
import Stackage.Util
|
||||
import Stackage.Config
|
||||
import System.Directory (doesDirectoryExist, removeDirectoryRecursive, removeFile, createDirectory)
|
||||
import System.Process (readProcess, waitForProcess, runProcess)
|
||||
import System.Exit (ExitCode (ExitSuccess), exitWith)
|
||||
@ -18,26 +18,10 @@ import System.IO (IOMode (WriteMode, AppendMode), withBinaryFile)
|
||||
data Mismatch = OnlyDryRun String | OnlySimpleList String
|
||||
deriving Show
|
||||
|
||||
extraCore :: Set PackageName
|
||||
extraCore = Set.singleton $ PackageName "binary"
|
||||
|
||||
-- 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.
|
||||
expectedFailures :: Set PackageName
|
||||
expectedFailures = Set.fromList $ map PackageName
|
||||
[ -- Requires an old version of WAI and Warp for tests
|
||||
"HTTP"
|
||||
-- Requires a special hspec-meta which is not yet available from
|
||||
-- Hackage.
|
||||
, "hspec"
|
||||
]
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
userPackages <- loadPackageList "package-list.txt"
|
||||
hp <- loadHaskellPlatform
|
||||
let allPackages = Map.union userPackages $ identsToRanges (hplibs hp)
|
||||
let allPackages = Map.union stablePackages $ identsToRanges (hplibs hp)
|
||||
pdb <- loadPackageDB (extraCore `Set.union` Set.map (\(PackageIdentifier p _) -> p) (hpcore hp)) allPackages
|
||||
final <- narrowPackageDB pdb $ Set.fromList $ Map.keys allPackages
|
||||
let simpleList = map (\(PackageName p, v) -> p ++ "-" ++ showVersion v) $ Map.toList final
|
||||
|
||||
@ -1,10 +0,0 @@
|
||||
-- Michael Snoyman michael@snoyman.com
|
||||
yesod < 1.4
|
||||
yesod-newsfeed
|
||||
yesod-sitemap
|
||||
yesod-static
|
||||
|
||||
-- Extra dependencies not caught otherwise
|
||||
cipher-aes
|
||||
hinotify
|
||||
unix-time
|
||||
@ -15,12 +15,12 @@ build-type: Simple
|
||||
cabal-version: >=1.8
|
||||
|
||||
library
|
||||
exposed-modules: Stackage.PackageList
|
||||
Stackage.NarrowDatabase
|
||||
exposed-modules: Stackage.NarrowDatabase
|
||||
Stackage.LoadDatabase
|
||||
Stackage.HaskellPlatform
|
||||
Stackage.Util
|
||||
Stackage.Types
|
||||
Stackage.Config
|
||||
build-depends: base >= 4 && < 5
|
||||
, containers
|
||||
, Cabal
|
||||
@ -28,6 +28,7 @@ library
|
||||
, bytestring
|
||||
, directory
|
||||
, filepath
|
||||
, transformers
|
||||
|
||||
executable stackage-gen-install-line
|
||||
hs-source-dirs: app
|
||||
|
||||
Loading…
Reference in New Issue
Block a user