mirror of
https://github.com/commercialhaskell/stackage.git
synced 2026-01-12 15:28:29 +01:00
Removed some outdated patches
This commit is contained in:
parent
521a71501f
commit
ea2e4fb733
@ -1,19 +0,0 @@
|
||||
diff -ru orig/async.cabal new/async.cabal
|
||||
--- orig/async.cabal 2013-12-09 14:04:55.984162531 +0200
|
||||
+++ new/async.cabal 2013-12-09 14:04:55.000000000 +0200
|
||||
@@ -70,13 +70,13 @@
|
||||
|
||||
library
|
||||
exposed-modules: Control.Concurrent.Async
|
||||
- build-depends: base >= 4.3 && < 4.7, stm >= 2.2 && < 2.5
|
||||
+ build-depends: base >= 4.3 && < 4.8, stm >= 2.2 && < 2.5
|
||||
|
||||
test-suite test-async
|
||||
type: exitcode-stdio-1.0
|
||||
hs-source-dirs: test
|
||||
main-is: test-async.hs
|
||||
- build-depends: base >= 4.3 && < 4.7,
|
||||
+ build-depends: base >= 4.3 && < 4.8,
|
||||
async,
|
||||
test-framework,
|
||||
test-framework-hunit,
|
||||
@ -1,143 +0,0 @@
|
||||
diff -ru orig/Aws/Core.hs new/Aws/Core.hs
|
||||
--- orig/Aws/Core.hs 2013-12-04 07:33:52.794606590 +0200
|
||||
+++ new/Aws/Core.hs 2013-12-04 07:33:51.000000000 +0200
|
||||
@@ -104,6 +104,8 @@
|
||||
import Data.Char
|
||||
import Data.Conduit (ResourceT, ($$+-))
|
||||
import qualified Data.Conduit as C
|
||||
+import qualified Data.Conduit.List as CL
|
||||
+import Data.Default (def)
|
||||
import Data.IORef
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
@@ -186,7 +188,11 @@
|
||||
-- | Does not parse response. For debugging.
|
||||
instance ResponseConsumer r (HTTP.Response L.ByteString) where
|
||||
type ResponseMetadata (HTTP.Response L.ByteString) = ()
|
||||
- responseConsumer _ _ resp = HTTP.lbsResponse resp
|
||||
+ responseConsumer _ _ resp = do
|
||||
+ bss <- HTTP.responseBody resp $$+- CL.consume
|
||||
+ return resp
|
||||
+ { HTTP.responseBody = L.fromChunks bss
|
||||
+ }
|
||||
|
||||
-- | Class for responses that are fully loaded into memory
|
||||
class AsMemoryResponse resp where
|
||||
@@ -340,16 +346,24 @@
|
||||
-- | Additional non-"amz" headers.
|
||||
, sqOtherHeaders :: HTTP.RequestHeaders
|
||||
-- | Request body (used with 'Post' and 'Put').
|
||||
+#if MIN_VERSION_http_conduit(2, 0, 0)
|
||||
+ , sqBody :: Maybe HTTP.RequestBody
|
||||
+#else
|
||||
, sqBody :: Maybe (HTTP.RequestBody (C.ResourceT IO))
|
||||
+#endif
|
||||
-- | String to sign. Note that the string is already signed, this is passed mostly for debugging purposes.
|
||||
, sqStringToSign :: B.ByteString
|
||||
}
|
||||
--deriving (Show)
|
||||
|
||||
-- | Create a HTTP request from a 'SignedQuery' object.
|
||||
+#if MIN_VERSION_http_conduit(2, 0, 0)
|
||||
+queryToHttpRequest :: SignedQuery -> HTTP.Request
|
||||
+#else
|
||||
queryToHttpRequest :: SignedQuery -> HTTP.Request (C.ResourceT IO)
|
||||
+#endif
|
||||
queryToHttpRequest SignedQuery{..}
|
||||
- = HTTP.def {
|
||||
+ = def {
|
||||
HTTP.method = httpMethod sqMethod
|
||||
, HTTP.secure = case sqProtocol of
|
||||
HTTP -> False
|
||||
diff -ru orig/Aws/S3/Commands/GetObject.hs new/Aws/S3/Commands/GetObject.hs
|
||||
--- orig/Aws/S3/Commands/GetObject.hs 2013-12-04 07:33:52.794606590 +0200
|
||||
+++ new/Aws/S3/Commands/GetObject.hs 2013-12-04 07:33:51.000000000 +0200
|
||||
@@ -9,6 +9,7 @@
|
||||
import qualified Data.ByteString.Char8 as B8
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.Conduit as C
|
||||
+import qualified Data.Conduit.List as CL
|
||||
import Data.Maybe
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as T
|
||||
@@ -81,4 +82,8 @@
|
||||
|
||||
instance AsMemoryResponse GetObjectResponse where
|
||||
type MemoryResponse GetObjectResponse = GetObjectMemoryResponse
|
||||
- loadToMemory (GetObjectResponse om x) = GetObjectMemoryResponse om <$> HTTP.lbsResponse x
|
||||
+ loadToMemory (GetObjectResponse om x) = do
|
||||
+ bss <- HTTP.responseBody x C.$$+- CL.consume
|
||||
+ return $ GetObjectMemoryResponse om x
|
||||
+ { HTTP.responseBody = L.fromChunks bss
|
||||
+ }
|
||||
diff -ru orig/Aws/S3/Commands/PutObject.hs new/Aws/S3/Commands/PutObject.hs
|
||||
--- orig/Aws/S3/Commands/PutObject.hs 2013-12-04 07:33:52.794606590 +0200
|
||||
+++ new/Aws/S3/Commands/PutObject.hs 2013-12-04 07:33:51.000000000 +0200
|
||||
@@ -1,3 +1,4 @@
|
||||
+{-# LANGUAGE CPP #-}
|
||||
module Aws.S3.Commands.PutObject
|
||||
where
|
||||
|
||||
@@ -27,11 +28,19 @@
|
||||
poAcl :: Maybe CannedAcl,
|
||||
poStorageClass :: Maybe StorageClass,
|
||||
poWebsiteRedirectLocation :: Maybe T.Text,
|
||||
+#if MIN_VERSION_http_conduit(2, 0, 0)
|
||||
+ poRequestBody :: HTTP.RequestBody,
|
||||
+#else
|
||||
poRequestBody :: HTTP.RequestBody (C.ResourceT IO),
|
||||
+#endif
|
||||
poMetadata :: [(T.Text,T.Text)]
|
||||
}
|
||||
|
||||
+#if MIN_VERSION_http_conduit(2, 0, 0)
|
||||
+putObject :: Bucket -> T.Text -> HTTP.RequestBody -> PutObject
|
||||
+#else
|
||||
putObject :: Bucket -> T.Text -> HTTP.RequestBody (C.ResourceT IO) -> PutObject
|
||||
+#endif
|
||||
putObject bucket obj body = PutObject obj bucket Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing body []
|
||||
|
||||
data PutObjectResponse
|
||||
@@ -75,4 +84,4 @@
|
||||
|
||||
instance AsMemoryResponse PutObjectResponse where
|
||||
type MemoryResponse PutObjectResponse = PutObjectResponse
|
||||
- loadToMemory = return
|
||||
\ No newline at end of file
|
||||
+ loadToMemory = return
|
||||
diff -ru orig/Aws/S3/Core.hs new/Aws/S3/Core.hs
|
||||
--- orig/Aws/S3/Core.hs 2013-12-04 07:33:52.794606590 +0200
|
||||
+++ new/Aws/S3/Core.hs 2013-12-04 07:33:51.000000000 +0200
|
||||
@@ -1,3 +1,4 @@
|
||||
+{-# LANGUAGE CPP #-}
|
||||
module Aws.S3.Core where
|
||||
|
||||
import Aws.Core
|
||||
@@ -137,7 +138,11 @@
|
||||
, s3QContentMd5 :: Maybe MD5
|
||||
, s3QAmzHeaders :: HTTP.RequestHeaders
|
||||
, s3QOtherHeaders :: HTTP.RequestHeaders
|
||||
+#if MIN_VERSION_http_conduit(2, 0, 0)
|
||||
+ , s3QRequestBody :: Maybe HTTP.RequestBody
|
||||
+#else
|
||||
, s3QRequestBody :: Maybe (HTTP.RequestBody (C.ResourceT IO))
|
||||
+#endif
|
||||
}
|
||||
|
||||
instance Show S3Query where
|
||||
diff -ru orig/aws.cabal new/aws.cabal
|
||||
--- orig/aws.cabal 2013-12-04 07:33:52.802606590 +0200
|
||||
+++ new/aws.cabal 2013-12-04 07:33:51.000000000 +0200
|
||||
@@ -107,10 +107,11 @@
|
||||
crypto-api >= 0.9,
|
||||
cryptohash >= 0.8 && < 0.12,
|
||||
cryptohash-cryptoapi == 0.1.*,
|
||||
+ data-default == 0.5.*,
|
||||
directory >= 1.0 && < 1.3,
|
||||
failure >= 0.2.0.1 && < 0.3,
|
||||
filepath >= 1.1 && < 1.4,
|
||||
- http-conduit >= 1.9 && < 1.10,
|
||||
+ http-conduit >= 1.9 && < 2.1,
|
||||
http-types >= 0.7 && < 0.9,
|
||||
lifted-base >= 0.1 && < 0.3,
|
||||
monad-control >= 0.3,
|
||||
@ -1,150 +0,0 @@
|
||||
diff -ru orig/Gtk2HsSetup.hs new/Gtk2HsSetup.hs
|
||||
--- orig/Gtk2HsSetup.hs 2013-10-28 08:36:50.283581635 +0100
|
||||
+++ new/Gtk2HsSetup.hs 2013-10-28 08:36:50.000000000 +0100
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE CPP #-}
|
||||
+{-# LANGUAGE CPP, ViewPatterns #-}
|
||||
|
||||
#ifndef CABAL_VERSION_CHECK
|
||||
#error This module has to be compiled via the Setup.hs program which generates the gtk2hs-macros.h file
|
||||
@@ -29,7 +29,7 @@
|
||||
emptyBuildInfo, allBuildInfo,
|
||||
Library(..),
|
||||
libModules, hasLibs)
|
||||
-import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..),
|
||||
+import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(withPackageDB, buildDir, localPkgDescr, installedPkgs, withPrograms),
|
||||
InstallDirs(..),
|
||||
componentPackageDeps,
|
||||
absoluteInstallDirs)
|
||||
@@ -56,14 +56,26 @@
|
||||
import Distribution.Verbosity
|
||||
import Control.Monad (when, unless, filterM, liftM, forM, forM_)
|
||||
import Data.Maybe ( isJust, isNothing, fromMaybe, maybeToList )
|
||||
-import Data.List (isPrefixOf, isSuffixOf, nub, minimumBy)
|
||||
+import Data.List (isPrefixOf, isSuffixOf, nub, minimumBy, stripPrefix)
|
||||
import Data.Ord as Ord (comparing)
|
||||
-import Data.Char (isAlpha)
|
||||
+import Data.Char (isAlpha, isNumber)
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
+import qualified Distribution.Simple.LocalBuildInfo as LBI
|
||||
|
||||
import Control.Applicative ((<$>))
|
||||
|
||||
+#if CABAL_VERSION_CHECK(1,17,0)
|
||||
+import Distribution.Simple.Program.Find ( defaultProgramSearchPath )
|
||||
+onDefaultSearchPath f a b = f a b defaultProgramSearchPath
|
||||
+libraryConfig lbi = case [clbi | (LBI.CLibName, clbi, _) <- LBI.componentsConfigs lbi] of
|
||||
+ [clbi] -> Just clbi
|
||||
+ _ -> Nothing
|
||||
+#else
|
||||
+onDefaultSearchPath = id
|
||||
+libraryConfig = LBI.libraryConfig
|
||||
+#endif
|
||||
+
|
||||
-- the name of the c2hs pre-compiled header file
|
||||
precompFile = "precompchs.bin"
|
||||
|
||||
@@ -100,7 +112,7 @@
|
||||
|
||||
fixLibs :: [FilePath] -> [String] -> [String]
|
||||
fixLibs dlls = concatMap $ \ lib ->
|
||||
- case filter (("lib" ++ lib) `isPrefixOf`) dlls of
|
||||
+ case filter (isLib lib) dlls of
|
||||
dlls@(_:_) -> [dropExtension (pickDll dlls)]
|
||||
_ -> if lib == "z" then [] else [lib]
|
||||
where
|
||||
@@ -111,7 +123,12 @@
|
||||
-- Yes this is a hack but the proper solution is hard: we would need to
|
||||
-- parse the .a file and see which .dll file(s) it needed to link to.
|
||||
pickDll = minimumBy (Ord.comparing length)
|
||||
-
|
||||
+ isLib lib dll =
|
||||
+ case stripPrefix ("lib"++lib) dll of
|
||||
+ Just ('.':_) -> True
|
||||
+ Just ('-':n:_) | isNumber n -> True
|
||||
+ _ -> False
|
||||
+
|
||||
-- The following code is a big copy-and-paste job from the sources of
|
||||
-- Cabal 1.8 just to be able to fix a field in the package file. Yuck.
|
||||
|
||||
@@ -144,8 +161,8 @@
|
||||
register :: PackageDescription -> LocalBuildInfo
|
||||
-> RegisterFlags -- ^Install in the user's database?; verbose
|
||||
-> IO ()
|
||||
-register pkg@PackageDescription { library = Just lib }
|
||||
- lbi@LocalBuildInfo { libraryConfig = Just clbi } regFlags
|
||||
+register pkg@(library -> Just lib )
|
||||
+ lbi@(libraryConfig -> Just clbi) regFlags
|
||||
= do
|
||||
|
||||
installedPkgInfoRaw <- generateRegistrationInfo
|
||||
@@ -237,6 +254,7 @@
|
||||
= nub $
|
||||
["-I" ++ dir | dir <- PD.includeDirs bi]
|
||||
++ [opt | opt@('-':c:_) <- PD.cppOptions bi ++ PD.ccOptions bi, c `elem` "DIU"]
|
||||
+ ++ ["-D__GLASGOW_HASKELL__="++show __GLASGOW_HASKELL__]
|
||||
|
||||
installCHI :: PackageDescription -- ^information from the .cabal file
|
||||
-> LocalBuildInfo -- ^information from the configure step
|
||||
@@ -426,7 +444,7 @@
|
||||
checkGtk2hsBuildtools :: [Program] -> IO ()
|
||||
checkGtk2hsBuildtools programs = do
|
||||
programInfos <- mapM (\ prog -> do
|
||||
- location <- programFindLocation prog normal
|
||||
+ location <- onDefaultSearchPath programFindLocation prog normal
|
||||
return (programName prog, location)
|
||||
) programs
|
||||
let printError name = do
|
||||
diff -ru orig/SetupWrapper.hs new/SetupWrapper.hs
|
||||
--- orig/SetupWrapper.hs 2013-10-28 08:36:50.283581635 +0100
|
||||
+++ new/SetupWrapper.hs 2013-10-28 08:36:50.000000000 +0100
|
||||
@@ -29,6 +29,24 @@
|
||||
import Control.Monad
|
||||
|
||||
|
||||
+-- moreRecentFile is implemented in Distribution.Simple.Utils, but only in
|
||||
+-- Cabal >= 1.18. For backwards-compatibility, we implement a copy with a new
|
||||
+-- name here. Some desirable alternate strategies don't work:
|
||||
+-- * We can't use CPP to check which version of Cabal we're up against because
|
||||
+-- this is the file that's generating the macros for doing that.
|
||||
+-- * We can't use the name moreRecentFiles and use
|
||||
+-- import D.S.U hiding (moreRecentFiles)
|
||||
+-- because on old GHC's (and according to the Report) hiding a name that
|
||||
+-- doesn't exist is an error.
|
||||
+moreRecentFile' :: FilePath -> FilePath -> IO Bool
|
||||
+moreRecentFile' a b = do
|
||||
+ exists <- doesFileExist b
|
||||
+ if not exists
|
||||
+ then return True
|
||||
+ else do tb <- getModificationTime b
|
||||
+ ta <- getModificationTime a
|
||||
+ return (ta > tb)
|
||||
+
|
||||
setupWrapper :: FilePath -> IO ()
|
||||
setupWrapper setupHsFile = do
|
||||
args <- getArgs
|
||||
@@ -91,8 +109,8 @@
|
||||
-- Currently this is GHC only. It should really be generalised.
|
||||
--
|
||||
compileSetupExecutable = do
|
||||
- setupHsNewer <- setupHsFile `moreRecentFile` setupProgFile
|
||||
- cabalVersionNewer <- setupVersionFile `moreRecentFile` setupProgFile
|
||||
+ setupHsNewer <- setupHsFile `moreRecentFile'` setupProgFile
|
||||
+ cabalVersionNewer <- setupVersionFile `moreRecentFile'` setupProgFile
|
||||
let outOfDate = setupHsNewer || cabalVersionNewer
|
||||
when outOfDate $ do
|
||||
debug verbosity "Setup script is out of date, compiling..."
|
||||
@@ -144,12 +162,3 @@
|
||||
Nothing Nothing Nothing
|
||||
exitCode <- waitForProcess process
|
||||
unless (exitCode == ExitSuccess) $ exitWith exitCode
|
||||
-
|
||||
-moreRecentFile :: FilePath -> FilePath -> IO Bool
|
||||
-moreRecentFile a b = do
|
||||
- exists <- doesFileExist b
|
||||
- if not exists
|
||||
- then return True
|
||||
- else do tb <- getModificationTime b
|
||||
- ta <- getModificationTime a
|
||||
- return (ta > tb)
|
||||
@ -1,23 +0,0 @@
|
||||
diff -ru orig/esqueleto.cabal new/esqueleto.cabal
|
||||
--- orig/esqueleto.cabal 2013-12-26 14:17:58.627602427 +0200
|
||||
+++ new/esqueleto.cabal 2013-12-26 14:17:58.000000000 +0200
|
||||
@@ -57,7 +57,7 @@
|
||||
build-depends:
|
||||
base >= 4.5 && < 4.7
|
||||
, text == 0.11.*
|
||||
- , persistent == 1.2.*
|
||||
+ , persistent >= 1.2 && < 1.4
|
||||
, transformers >= 0.2
|
||||
, unordered-containers >= 0.2
|
||||
, tagged >= 0.2
|
||||
@@ -83,8 +83,8 @@
|
||||
, HUnit
|
||||
, QuickCheck
|
||||
, hspec >= 1.3 && < 1.8
|
||||
- , persistent-sqlite == 1.2.*
|
||||
- , persistent-template == 1.2.*
|
||||
+ , persistent-sqlite >= 1.2 && < 1.4
|
||||
+ , persistent-template >= 1.2 && < 1.4
|
||||
, monad-control
|
||||
, monad-logger >= 0.3
|
||||
|
||||
@ -1,19 +0,0 @@
|
||||
diff -ru orig/System/Log/FastLogger/Logger.hs new/System/Log/FastLogger/Logger.hs
|
||||
--- orig/System/Log/FastLogger/Logger.hs 2013-12-24 08:14:25.325658733 +0200
|
||||
+++ new/System/Log/FastLogger/Logger.hs 2013-12-24 08:14:24.000000000 +0200
|
||||
@@ -19,6 +19,15 @@
|
||||
|
||||
data Logger = Logger (MVar Buffer) !BufSize (IORef LogStr)
|
||||
|
||||
+#if !MIN_VERSION_base(4, 6, 0)
|
||||
+atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
|
||||
+atomicModifyIORef' ref f = do
|
||||
+ b <- atomicModifyIORef ref
|
||||
+ (\x -> let (a, b) = f x
|
||||
+ in (a, a `seq` b))
|
||||
+ b `seq` return b
|
||||
+#endif
|
||||
+
|
||||
newLogger :: BufSize -> IO Logger
|
||||
newLogger size = do
|
||||
buf <- getBuffer size
|
||||
@ -1,12 +0,0 @@
|
||||
diff -ru orig/System/Log/FastLogger.hs new/System/Log/FastLogger.hs
|
||||
--- orig/System/Log/FastLogger.hs 2013-12-24 10:23:27.725895194 +0200
|
||||
+++ new/System/Log/FastLogger.hs 2013-12-24 10:23:27.000000000 +0200
|
||||
@@ -13,6 +13,8 @@
|
||||
-- * Log messages
|
||||
, LogStr
|
||||
, ToLogStr(..)
|
||||
+ , logStrLength
|
||||
+ , logStrBuilder
|
||||
-- * Writing a log message
|
||||
, pushLogStr
|
||||
-- * Flushing buffered log messages
|
||||
@ -1,32 +0,0 @@
|
||||
diff -ru orig/src/main/Main.hs new/src/main/Main.hs
|
||||
--- orig/src/main/Main.hs 2013-10-14 09:10:24.895239824 +0300
|
||||
+++ new/src/main/Main.hs 2013-10-14 09:10:24.000000000 +0300
|
||||
@@ -1,3 +1,4 @@
|
||||
+{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
-- | Main compiler executable.
|
||||
@@ -15,6 +16,9 @@
|
||||
import Data.Maybe
|
||||
import Data.Version (showVersion)
|
||||
import Options.Applicative
|
||||
+#if MIN_VERSION_optparse_applicative(0,6,0)
|
||||
+import Options.Applicative.Types
|
||||
+#endif
|
||||
import System.Environment
|
||||
|
||||
-- | Options and help.
|
||||
@@ -119,8 +123,13 @@
|
||||
<*> switch (long "typecheck-only" <> help "Only invoke GHC for typechecking, don't produce any output")
|
||||
<*> optional (strOption $ long "runtime-path" <> help "Custom path to the runtime so you don't have to reinstall fay when modifying it")
|
||||
|
||||
+
|
||||
where strsOption m =
|
||||
+#if MIN_VERSION_optparse_applicative(0,6,0)
|
||||
+ nullOption (m <> reader (ReadM . Right . wordsBy (== ',')) <> value [])
|
||||
+#else
|
||||
nullOption (m <> reader (Right . wordsBy (== ',')) <> value [])
|
||||
+#endif
|
||||
|
||||
|
||||
-- | Make incompatible options.
|
||||
@ -1,72 +0,0 @@
|
||||
diff -ru orig/src/General/Web.hs new/src/General/Web.hs
|
||||
--- orig/src/General/Web.hs 2013-12-04 19:36:25.387122831 +0200
|
||||
+++ new/src/General/Web.hs 2013-12-04 19:36:25.000000000 +0200
|
||||
@@ -1,3 +1,4 @@
|
||||
+{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
|
||||
{- |
|
||||
@@ -15,6 +16,9 @@
|
||||
import General.System
|
||||
import General.Base
|
||||
import Network.Wai
|
||||
+#if MIN_VERSION_wai(2, 0, 0)
|
||||
+import Network.Wai.Internal
|
||||
+#endif
|
||||
import Network.HTTP.Types
|
||||
import Data.CaseInsensitive(original)
|
||||
import qualified Data.ByteString.Lazy.Char8 as LBS
|
||||
@@ -34,10 +38,17 @@
|
||||
|
||||
responseFlatten :: Response -> IO (Status, ResponseHeaders, LBString)
|
||||
responseFlatten r = do
|
||||
+#if MIN_VERSION_wai(2, 0, 0)
|
||||
+ let (s,hs,withSrc) = responseToSource r
|
||||
+ chunks <- withSrc $ \src -> src $$ consume
|
||||
+ let res = toLazyByteString $ mconcat [x | Chunk x <- chunks]
|
||||
+ return (s,hs,res)
|
||||
+#else
|
||||
let (s,hs,rest) = responseSource r
|
||||
chunks <- runResourceT $ rest $$ consume
|
||||
let res = toLazyByteString $ mconcat [x | Chunk x <- chunks]
|
||||
return (s,hs,res)
|
||||
+#endif
|
||||
|
||||
|
||||
responseEvaluate :: Response -> IO ()
|
||||
diff -ru orig/src/Web/Server.hs new/src/Web/Server.hs
|
||||
--- orig/src/Web/Server.hs 2013-12-04 19:36:25.379122832 +0200
|
||||
+++ new/src/Web/Server.hs 2013-12-04 19:36:25.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE RecordWildCards, ScopedTypeVariables, PatternGuards #-}
|
||||
+{-# LANGUAGE RecordWildCards, ScopedTypeVariables, PatternGuards, CPP #-}
|
||||
|
||||
module Web.Server(server) where
|
||||
|
||||
@@ -16,6 +16,9 @@
|
||||
import Data.Time.Clock
|
||||
|
||||
import Network.Wai
|
||||
+#if MIN_VERSION_wai(2, 0, 0)
|
||||
+import Network.Wai.Internal
|
||||
+#endif
|
||||
import Network.Wai.Handler.Warp
|
||||
|
||||
|
||||
@@ -34,9 +37,15 @@
|
||||
return res
|
||||
|
||||
|
||||
+#if MIN_VERSION_wai(2, 0, 0)
|
||||
+exception :: Maybe Request -> SomeException -> IO ()
|
||||
+exception _ e | Just (_ :: InvalidRequest) <- fromException e = return ()
|
||||
+ | otherwise = putStrLn $ "Error: " ++ show e
|
||||
+#else
|
||||
exception :: SomeException -> IO ()
|
||||
exception e | Just (_ :: InvalidRequest) <- fromException e = return ()
|
||||
| otherwise = putStrLn $ "Error: " ++ show e
|
||||
+#endif
|
||||
|
||||
|
||||
respArgs :: CmdLine -> IO (IO ResponseArgs)
|
||||
Only in orig: test
|
||||
@ -1,12 +0,0 @@
|
||||
diff -ru orig/Network/Shed/Httpd.hs new/Network/Shed/Httpd.hs
|
||||
--- orig/Network/Shed/Httpd.hs 2013-10-10 10:19:03.153688450 +0300
|
||||
+++ new/Network/Shed/Httpd.hs 2013-10-10 10:19:02.000000000 +0300
|
||||
@@ -139,7 +139,7 @@
|
||||
hClose h
|
||||
_ -> hClose h
|
||||
return ()
|
||||
- ) `finally` sClose sock
|
||||
+ ) `finally` Network.Socket.sClose sock
|
||||
where
|
||||
loopIO m = do m
|
||||
loopIO m
|
||||
@ -1,47 +0,0 @@
|
||||
diff -ru orig/io-streams.cabal new/io-streams.cabal
|
||||
--- orig/io-streams.cabal 2013-12-24 06:42:56.449491097 +0200
|
||||
+++ new/io-streams.cabal 2013-12-24 06:42:56.000000000 +0200
|
||||
@@ -162,7 +162,7 @@
|
||||
attoparsec >= 0.10 && <0.11,
|
||||
blaze-builder >= 0.3.1 && <0.4,
|
||||
bytestring >= 0.9 && <0.11,
|
||||
- network >= 2.4 && <2.5,
|
||||
+ network >= 2.3 && <2.5,
|
||||
primitive >= 0.2 && <0.6,
|
||||
process >= 1 && <1.3,
|
||||
text >= 0.10 && <1.1,
|
||||
@@ -246,7 +246,7 @@
|
||||
directory >= 1.1 && <2,
|
||||
filepath >= 1.2 && <2,
|
||||
mtl >= 2 && <3,
|
||||
- network >= 2.4 && <2.5,
|
||||
+ network >= 2.3 && <2.5,
|
||||
primitive >= 0.2 && <0.6,
|
||||
process >= 1 && <1.3,
|
||||
text >= 0.10 && <1.1,
|
||||
diff -ru orig/test/System/IO/Streams/Tests/Network.hs new/test/System/IO/Streams/Tests/Network.hs
|
||||
--- orig/test/System/IO/Streams/Tests/Network.hs 2013-12-24 06:42:56.441491095 +0200
|
||||
+++ new/test/System/IO/Streams/Tests/Network.hs 2013-12-24 06:42:56.000000000 +0200
|
||||
@@ -44,18 +44,18 @@
|
||||
Streams.fromList ["", "ok"] >>= Streams.connectTo os
|
||||
N.shutdown sock N.ShutdownSend
|
||||
Streams.toList is >>= putMVar resultMVar
|
||||
- N.close sock
|
||||
+ N.sClose sock
|
||||
|
||||
server mvar = do
|
||||
sock <- N.socket N.AF_INET N.Stream N.defaultProtocol
|
||||
addr <- N.inet_addr "127.0.0.1"
|
||||
let saddr = N.SockAddrInet N.aNY_PORT addr
|
||||
- N.bind sock saddr
|
||||
+ N.bindSocket sock saddr
|
||||
N.listen sock 5
|
||||
port <- N.socketPort sock
|
||||
putMVar mvar port
|
||||
(csock, _) <- N.accept sock
|
||||
(is, os) <- Streams.socketToStreams csock
|
||||
Streams.toList is >>= flip Streams.writeList os
|
||||
- N.close csock
|
||||
- N.close sock
|
||||
+ N.sClose csock
|
||||
+ N.sClose sock
|
||||
@ -1,39 +0,0 @@
|
||||
Only in new: dist
|
||||
diff -ru orig/language-javascript.cabal new/language-javascript.cabal
|
||||
--- orig/language-javascript.cabal 2013-12-09 14:11:28.596175378 +0200
|
||||
+++ new/language-javascript.cabal 2013-12-09 14:11:28.000000000 +0200
|
||||
@@ -30,7 +30,7 @@
|
||||
|
||||
Library
|
||||
Build-depends: base >= 4 && < 5
|
||||
- , array >= 0.3 && < 0.5
|
||||
+ , array >= 0.3 && < 0.6
|
||||
, mtl >= 1.1 && < 2.9
|
||||
, containers >= 0.2 && < 0.6
|
||||
, utf8-light >= 0.4 && < 1.0
|
||||
diff -ru orig/src/Language/JavaScript/Parser/Lexer.hs new/src/Language/JavaScript/Parser/Lexer.hs
|
||||
--- orig/src/Language/JavaScript/Parser/Lexer.hs 2013-12-09 14:11:28.592175378 +0200
|
||||
+++ new/src/Language/JavaScript/Parser/Lexer.hs 2013-12-09 14:11:27.000000000 +0200
|
||||
@@ -1,4 +1,4 @@
|
||||
-{-# LANGUAGE CPP,MagicHash #-}
|
||||
+{-# LANGUAGE BangPatterns, CPP,MagicHash #-}
|
||||
{-# LINE 1 "src-dev/Language/JavaScript/Parser/Lexer.x" #-}
|
||||
|
||||
|
||||
@@ -708,11 +708,15 @@
|
||||
|
||||
let
|
||||
(base) = alexIndexInt32OffAddr alex_base s
|
||||
- ((I# (ord_c))) = fromIntegral c
|
||||
+ !((I# (ord_c))) = fromIntegral c
|
||||
(offset) = (base +# ord_c)
|
||||
(check) = alexIndexInt16OffAddr alex_check offset
|
||||
|
||||
+#if MIN_VERSION_base(4, 7, 0)
|
||||
+ (new_s) = if (I# (offset >=# 0#) /= 0) && (I# (check ==# ord_c) /= 0)
|
||||
+#else
|
||||
(new_s) = if (offset >=# 0#) && (check ==# ord_c)
|
||||
+#endif
|
||||
then alexIndexInt16OffAddr alex_table offset
|
||||
else alexIndexInt16OffAddr alex_deflt s
|
||||
in
|
||||
@ -1,34 +0,0 @@
|
||||
diff -ru orig/Control/Exception/Peel.hs new/Control/Exception/Peel.hs
|
||||
--- orig/Control/Exception/Peel.hs 2013-12-09 18:35:35.592693947 +0200
|
||||
+++ new/Control/Exception/Peel.hs 2013-12-09 18:35:35.000000000 +0200
|
||||
@@ -1,3 +1,4 @@
|
||||
+{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
|
||||
{- |
|
||||
@@ -20,7 +21,9 @@
|
||||
handle, handleJust,
|
||||
try, tryJust,
|
||||
evaluate,
|
||||
+#if !MIN_VERSION_base(4, 7, 0)
|
||||
block, unblock,
|
||||
+#endif
|
||||
bracket, bracket_, bracketOnError,
|
||||
finally, onException,
|
||||
) where
|
||||
@@ -108,6 +111,7 @@
|
||||
evaluate :: MonadIO m => a -> m a
|
||||
evaluate = liftIO . E.evaluate
|
||||
|
||||
+#if !MIN_VERSION_base(4, 7, 0)
|
||||
-- |Generalized version of 'E.block'.
|
||||
block :: MonadPeelIO m => m a -> m a
|
||||
block = liftIOOp_ E.block
|
||||
@@ -115,6 +119,7 @@
|
||||
-- |Generalized version of 'E.unblock'.
|
||||
unblock :: MonadPeelIO m => m a -> m a
|
||||
unblock = liftIOOp_ E.unblock
|
||||
+#endif
|
||||
|
||||
-- |Generalized version of 'E.bracket'. Note, any monadic side
|
||||
-- effects in @m@ of the \"release\" computation will be discarded; it
|
||||
@ -1,32 +0,0 @@
|
||||
diff -ru orig/Setup.lhs new/Setup.lhs
|
||||
--- orig/Setup.lhs 2013-10-10 10:21:21.877692795 +0300
|
||||
+++ new/Setup.lhs 2013-10-10 10:21:21.000000000 +0300
|
||||
@@ -2,6 +2,7 @@
|
||||
|
||||
\begin{code}
|
||||
{- OPTIONS_GHC -Wall #-}
|
||||
+{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
|
||||
|
||||
import Control.Monad (liftM2, mplus)
|
||||
import Data.List (isPrefixOf)
|
||||
@@ -22,8 +23,19 @@
|
||||
}
|
||||
}
|
||||
|
||||
+-- 'ConstOrId' is a Cabal compatibility hack.
|
||||
+-- see: https://github.com/scrive/hdbc-postgresql/commit/e9b2fbab07b8f55ae6a9e120ab0b98c433842a8b
|
||||
+class ConstOrId a b where
|
||||
+ constOrId :: a -> b
|
||||
+
|
||||
+instance ConstOrId a a where
|
||||
+ constOrId = id
|
||||
+
|
||||
+instance ConstOrId a (b -> a) where
|
||||
+ constOrId = const
|
||||
+
|
||||
mysqlConfigProgram = (simpleProgram "mysql_config") {
|
||||
- programFindLocation = \verbosity -> liftM2 mplus
|
||||
+ programFindLocation = \verbosity -> constOrId $ liftM2 mplus
|
||||
(findProgramLocation verbosity "mysql_config")
|
||||
(findProgramLocation verbosity "mysql_config5")
|
||||
}
|
||||
@ -1,47 +0,0 @@
|
||||
diff -ru orig/Crypto/PasswordStore.hs new/Crypto/PasswordStore.hs
|
||||
--- orig/Crypto/PasswordStore.hs 2013-09-17 11:48:49.178111970 +0300
|
||||
+++ new/Crypto/PasswordStore.hs 2013-09-17 11:48:49.000000000 +0300
|
||||
@@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE OverloadedStrings, BangPatterns #-}
|
||||
+{-# LANGUAGE CPP #-}
|
||||
-- |
|
||||
-- Module : Crypto.PasswordStore
|
||||
-- Copyright : (c) Peter Scott, 2011
|
||||
@@ -149,8 +150,8 @@
|
||||
-> ByteString
|
||||
-- ^ The encoded message
|
||||
hmacSHA256 secret msg =
|
||||
- let digest = SHA.hmacSha256 (BL.fromStrict secret) (BL.fromStrict msg)
|
||||
- in BL.toStrict . SHA.bytestringDigest $ digest
|
||||
+ let digest = SHA.hmacSha256 (fromStrict secret) (fromStrict msg)
|
||||
+ in toStrict . SHA.bytestringDigest $ digest
|
||||
|
||||
-- | PBKDF2 key-derivation function.
|
||||
-- For details see @http://tools.ietf.org/html/rfc2898@.
|
||||
@@ -403,3 +404,26 @@
|
||||
where (a, g') = randomR ('\NUL', '\255') g
|
||||
salt = makeSalt $ B.pack $ map fst (rands gen 16)
|
||||
newgen = snd $ last (rands gen 16)
|
||||
+
|
||||
+#if !MIN_VERSION_base(4, 6, 0)
|
||||
+-- | Strict version of 'modifySTRef'
|
||||
+modifySTRef' :: STRef s a -> (a -> a) -> ST s ()
|
||||
+modifySTRef' ref f = do
|
||||
+ x <- readSTRef ref
|
||||
+ let x' = f x
|
||||
+ x' `seq` writeSTRef ref x'
|
||||
+#endif
|
||||
+
|
||||
+#if MIN_VERSION_bytestring(0, 10, 0)
|
||||
+toStrict :: BL.ByteString -> BS.ByteString
|
||||
+toStrict = BL.toStrict
|
||||
+
|
||||
+fromStrict :: BS.ByteString -> BL.ByteString
|
||||
+fromStrict = BL.fromStrict
|
||||
+#else
|
||||
+toStrict :: BL.ByteString -> BS.ByteString
|
||||
+toStrict = BS.concat . BL.toChunks
|
||||
+
|
||||
+fromStrict :: BS.ByteString -> BL.ByteString
|
||||
+fromStrict = BL.fromChunks . return
|
||||
+#endif
|
||||
@ -1,43 +0,0 @@
|
||||
diff -ru orig/Test/Tasty/Options.hs new/Test/Tasty/Options.hs
|
||||
--- orig/Test/Tasty/Options.hs 2013-10-14 09:05:01.591238893 +0300
|
||||
+++ new/Test/Tasty/Options.hs 2013-10-14 09:05:01.000000000 +0300
|
||||
@@ -1,3 +1,4 @@
|
||||
+{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable,
|
||||
ExistentialQuantification, GADTs,
|
||||
OverlappingInstances, FlexibleInstances, UndecidableInstances,
|
||||
@@ -27,6 +28,9 @@
|
||||
import Data.Monoid
|
||||
|
||||
import Options.Applicative
|
||||
+#if MIN_VERSION_optparse_applicative(0,6,0)
|
||||
+import Options.Applicative.Types
|
||||
+#endif
|
||||
|
||||
-- | An option is a data type that inhabits the `IsOption` type class.
|
||||
class Typeable v => IsOption v where
|
||||
@@ -60,7 +64,11 @@
|
||||
name = untag (optionName :: Tagged v String)
|
||||
helpString = untag (optionHelp :: Tagged v String)
|
||||
parse =
|
||||
+#if MIN_VERSION_optparse_applicative(0,6,0)
|
||||
+ ReadM . maybe (Left (ErrorMsg $ "Could not parse " ++ name)) Right .
|
||||
+#else
|
||||
maybe (Left (ErrorMsg $ "Could not parse " ++ name)) Right .
|
||||
+#endif
|
||||
parseValue
|
||||
|
||||
|
||||
diff -ru orig/Test/Tasty/UI.hs new/Test/Tasty/UI.hs
|
||||
--- orig/Test/Tasty/UI.hs 2013-10-14 09:05:01.591238893 +0300
|
||||
+++ new/Test/Tasty/UI.hs 2013-10-14 09:05:01.000000000 +0300
|
||||
@@ -98,6 +98,9 @@
|
||||
|
||||
hSetBuffering stdout NoBuffering
|
||||
|
||||
+ -- Do not retain the reference to the tree more than necessary
|
||||
+ _ <- evaluate alignment
|
||||
+
|
||||
st <-
|
||||
flip execStateT initialState $ getApp $ fst $
|
||||
foldTestTree
|
||||
@ -1,12 +0,0 @@
|
||||
diff -ru orig/tasty.cabal new/tasty.cabal
|
||||
--- orig/tasty.cabal 2013-12-29 08:32:27.917648136 +0200
|
||||
+++ new/tasty.cabal 2013-12-29 08:32:27.000000000 +0200
|
||||
@@ -49,7 +49,7 @@
|
||||
regex-tdfa >= 1.1.8,
|
||||
optparse-applicative >= 0.6,
|
||||
deepseq >= 1.3,
|
||||
- either >= 4.0
|
||||
+ either >= 3.4.2
|
||||
|
||||
if flag(colors)
|
||||
build-depends: ansi-terminal >= 0.6.1
|
||||
@ -1,18 +0,0 @@
|
||||
diff -ru orig/src/Graphics/UI/Threepenny/Internal/Types.hs new/src/Graphics/UI/Threepenny/Internal/Types.hs
|
||||
--- orig/src/Graphics/UI/Threepenny/Internal/Types.hs 2013-12-24 06:45:49.129496370 +0200
|
||||
+++ new/src/Graphics/UI/Threepenny/Internal/Types.hs 2013-12-24 06:45:48.000000000 +0200
|
||||
@@ -37,7 +37,13 @@
|
||||
newtype ElementId = ElementId BS.ByteString
|
||||
deriving (Data,Typeable,Show,Eq,Ord)
|
||||
|
||||
-instance NFData ElementId where rnf (ElementId x) = rnf x
|
||||
+instance NFData ElementId where
|
||||
+ rnf (ElementId x) =
|
||||
+#if MIN_VERSION_bytestring(0, 10, 0)
|
||||
+ rnf x
|
||||
+#else
|
||||
+ BS.length x `seq` ()
|
||||
+#endif
|
||||
|
||||
type EventId = String
|
||||
type Handlers = Map EventId (E.Handler EventData)
|
||||
@ -1,43 +0,0 @@
|
||||
diff -ru orig/src/Codec/Binary/UTF8/Light.hs new/src/Codec/Binary/UTF8/Light.hs
|
||||
--- orig/src/Codec/Binary/UTF8/Light.hs 2013-10-15 09:40:45.447493856 +0300
|
||||
+++ new/src/Codec/Binary/UTF8/Light.hs 2013-10-15 09:40:45.000000000 +0300
|
||||
@@ -251,15 +251,27 @@
|
||||
-- can use Word# literalls
|
||||
-- ==> 0xff00ff00##
|
||||
encodeUTF8' ((W32# w):xs)
|
||||
+#if MIN_VERSION_base(4,7,0)
|
||||
+ | I# (w`ltWord#`(int2Word# 0x80#)) /= 0 =
|
||||
+#else
|
||||
| w`ltWord#`(int2Word# 0x80#) =
|
||||
+#endif
|
||||
[W8# w] : encodeUTF8' xs
|
||||
+#if MIN_VERSION_base(4,7,0)
|
||||
+ | I# (w`ltWord#`(int2Word# 0x800#)) /= 0 =
|
||||
+#else
|
||||
| w`ltWord#`(int2Word# 0x800#) =
|
||||
+#endif
|
||||
[ W8#(w`uncheckedShiftRL#`6#
|
||||
`or#`(int2Word# 0xc0#))
|
||||
, W8#(w`and#`(int2Word# 0x3f#)
|
||||
`or#`(int2Word# 0x80#))
|
||||
] : encodeUTF8' xs
|
||||
+#if MIN_VERSION_base(4,7,0)
|
||||
+ | I# (w`ltWord#`(int2Word# 0xf0000#)) /= 0 =
|
||||
+#else
|
||||
| w`ltWord#`(int2Word# 0xf0000#) =
|
||||
+#endif
|
||||
[ W8#(w`uncheckedShiftRL#`12#
|
||||
`or#`(int2Word# 0xe0#))
|
||||
, W8#(w`uncheckedShiftRL#`6#
|
||||
@@ -268,7 +280,11 @@
|
||||
, W8#(w`and#`(int2Word# 0x3f#)
|
||||
`or#`(int2Word# 0x80#))
|
||||
] : encodeUTF8' xs
|
||||
+#if MIN_VERSION_base(4,7,0)
|
||||
+ | I# (w`ltWord#`(int2Word# 0xe00000#)) /= 0 =
|
||||
+#else
|
||||
| w`ltWord#`(int2Word# 0xe00000#) =
|
||||
+#endif
|
||||
[ W8#(w`uncheckedShiftRL#`18#
|
||||
`or#`(int2Word# 0xf0#))
|
||||
, W8#(w`uncheckedShiftRL#`12#
|
||||
@ -1,30 +0,0 @@
|
||||
diff -ru orig/Data/UUID/Internal.hs new/Data/UUID/Internal.hs
|
||||
--- orig/Data/UUID/Internal.hs 2013-10-22 19:00:23.458184957 +0300
|
||||
+++ new/Data/UUID/Internal.hs 2013-10-22 19:00:23.000000000 +0300
|
||||
@@ -391,12 +391,24 @@
|
||||
|
||||
-- | Similar to `toASCIIBytes` except we produce a lazy `BL.ByteString`.
|
||||
toLazyASCIIBytes :: UUID -> BL.ByteString
|
||||
-toLazyASCIIBytes = BL.fromStrict . toASCIIBytes
|
||||
+toLazyASCIIBytes =
|
||||
+#if MIN_VERSION_bytestring(0,10,0)
|
||||
+ BL.fromStrict
|
||||
+#else
|
||||
+ BL.fromChunks . return
|
||||
+#endif
|
||||
+ . toASCIIBytes
|
||||
|
||||
-- | Similar to `fromASCIIBytes` except parses from a lazy `BL.ByteString`.
|
||||
fromLazyASCIIBytes :: BL.ByteString -> Maybe UUID
|
||||
fromLazyASCIIBytes bs =
|
||||
- if BL.length bs == 36 then fromASCIIBytes (BL.toStrict bs) else Nothing
|
||||
+ if BL.length bs == 36 then fromASCIIBytes (
|
||||
+#if MIN_VERSION_bytestring(0,10,0)
|
||||
+ BL.toStrict bs
|
||||
+#else
|
||||
+ B.concat $ BL.toChunks bs
|
||||
+#endif
|
||||
+ ) else Nothing
|
||||
|
||||
--
|
||||
-- Class Instances
|
||||
@ -1,13 +0,0 @@
|
||||
diff -ru orig/vault.cabal new/vault.cabal
|
||||
--- orig/vault.cabal 2013-09-01 18:35:14.861603037 +0300
|
||||
+++ new/vault.cabal 2013-09-01 18:35:14.000000000 +0300
|
||||
@@ -36,7 +36,8 @@
|
||||
|
||||
Library
|
||||
hs-source-dirs: src
|
||||
- build-depends: base == 4.6.*, containers == 0.5.*,
|
||||
+ build-depends: base >= 4.5 && < 4.7,
|
||||
+ containers >= 0.4 && < 0.6,
|
||||
unordered-containers >= 0.2.3.0 && < 0.3,
|
||||
hashable >= 1.1.2.5 && < 1.3
|
||||
|
||||
@ -1,12 +0,0 @@
|
||||
diff -ru orig/vault.cabal new/vault.cabal
|
||||
--- orig/vault.cabal 2013-12-09 14:04:56.244162539 +0200
|
||||
+++ new/vault.cabal 2013-12-09 14:04:56.000000000 +0200
|
||||
@@ -47,7 +47,7 @@
|
||||
|
||||
Library
|
||||
hs-source-dirs: src
|
||||
- build-depends: base >= 4.5 && < 4.7,
|
||||
+ build-depends: base >= 4.5 && < 4.8,
|
||||
containers >= 0.4 && < 0.6,
|
||||
unordered-containers >= 0.2.3.0 && < 0.3,
|
||||
hashable >= 1.1.2.5 && < 1.3
|
||||
@ -1,21 +0,0 @@
|
||||
diff -ru orig/websockets.cabal new/websockets.cabal
|
||||
--- orig/websockets.cabal 2013-09-12 10:30:46.697755480 +0300
|
||||
+++ new/websockets.cabal 2013-09-12 10:30:46.000000000 +0300
|
||||
@@ -73,7 +73,7 @@
|
||||
blaze-builder >= 0.3 && < 0.4,
|
||||
blaze-builder-enumerator >= 0.2 && < 0.3,
|
||||
bytestring >= 0.9 && < 0.11,
|
||||
- case-insensitive >= 0.3 && < 1.1,
|
||||
+ case-insensitive >= 0.3 && < 1.2,
|
||||
containers >= 0.3 && < 0.6,
|
||||
enumerator >= 0.4.13 && < 0.5,
|
||||
mtl >= 2.0 && < 2.2,
|
||||
@@ -106,7 +106,7 @@
|
||||
blaze-builder >= 0.3 && < 0.4,
|
||||
blaze-builder-enumerator >= 0.2 && < 0.3,
|
||||
bytestring >= 0.9 && < 0.11,
|
||||
- case-insensitive >= 0.3 && < 1.1,
|
||||
+ case-insensitive >= 0.3 && < 1.2,
|
||||
containers >= 0.3 && < 0.6,
|
||||
enumerator >= 0.4.13 && < 0.5,
|
||||
mtl >= 2.0 && < 2.2,
|
||||
Loading…
Reference in New Issue
Block a user