stackage/Stackage/Config.hs
Stefan Wehr 7cb16ddf84 Added my packages HTF, hscurses, xmlgen, and stm-stats
The HTF package require ./sandbox/bin to be in the PATH (HTF uses
the OPTIONS_GHC pragma to invoke cpphs with custom commandline
options).
2012-12-02 22:11:29 +01:00

86 lines
2.9 KiB
Haskell

{-# LANGUAGE CPP #-}
module Stackage.Config where
import Control.Monad.Trans.Writer (execWriter, tell)
import qualified Data.Map as Map
import Data.Set (fromList, singleton)
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 = 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.
defaultExpectedFailures :: Set PackageName
defaultExpectedFailures = 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"
-- text and setenv have recursive dependencies in their tests, which
-- cabal can't (yet) handle
, "text"
, "setenv"
-- The version of GLUT included with the HP does not generate
-- documentation correctly.
, "GLUT"
-- https://github.com/bos/statistics/issues/42
, "statistics"
-- https://github.com/kazu-yamamoto/unix-time/issues/4
, "unix-time"
-- https://github.com/kazu-yamamoto/simple-sendfile/pull/10
, "simple-sendfile"
-- https://github.com/alanz/hjsmin/pull/11
, "hjsmin"
-- Michael emailed Dominic about bumping version numbers, but no new
-- release has yet been made.
, "largeword"
]
-- | 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 = execWriter $ do
mapM_ (add "michael@snoyman.com") $ words
"yesod yesod-newsfeed yesod-sitemap yesod-static yesod-test markdown filesystem-conduit mime-mail-ses"
mapM_ (add "Neil Mitchell") $ words
"hoogle hlint"
mapM_ (add "Alan Zimmerman") $ words
"hjsmin language-javascript"
mapM_ (add "Jasper Van der Jeugt") $ words
"blaze-html blaze-markup stylish-haskell"
mapM_ (add "Antoine Latter") $ words
"uuid byteorder"
mapM (add "Stefan Wehr <wehr@factisresearch.com>") $ words
"HTF hscurses xmlgen stm-stats"
where
add maintainer package = addRange maintainer package "-any"
addRange maintainer package range =
case simpleParse range of
Nothing -> error $ "Invalid range " ++ show range ++ " for " ++ package
Just range' -> tell $ Map.singleton (PackageName package) (range', Maintainer maintainer)