diff --git a/patches/HsOpenSSL-0.11.4.11.patch b/patches/HsOpenSSL-0.11.4.11.patch deleted file mode 100644 index 0166b63dacc6f4cc6f2c8d361f0e7e03190c9fbc..0000000000000000000000000000000000000000 --- a/patches/HsOpenSSL-0.11.4.11.patch +++ /dev/null @@ -1,88 +0,0 @@ -From 73cc4b2894bb667cdeb63d7304616cf89bf70a68 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue, 23 Jan 2018 21:18:43 -0500 -Subject: [PATCH 1/2] Fix the build with GHC 8.4 - ---- - Setup.hs | 21 +++++++++++++++++++-- - 1 file changed, 19 insertions(+), 2 deletions(-) - -diff --git a/Setup.hs b/Setup.hs -index df711cf..8f27fde 100755 ---- a/Setup.hs -+++ b/Setup.hs -@@ -18,6 +18,12 @@ import Distribution.PackageDescription (FlagName(..), mkFlagName) - import Distribution.PackageDescription (FlagName(..)) - #endif - -+#if MIN_VERSION_Cabal(2,1,0) -+import Distribution.Types.GenericPackageDescription (mkFlagAssignment, unFlagAssignment) -+#else -+import Distribution.Types.GenericPackageDescription (FlagAssignment) -+#endif -+ - import Distribution.Verbosity (silent) - import System.Info (os) - import qualified Control.Exception as E (tryJust, throw) -@@ -29,6 +35,14 @@ import Data.List - mkFlagName = FlagName - #endif - -+#if !(MIN_VERSION_Cabal(2,1,0)) -+mkFlagAssignment :: [(FlagName, Bool)] -> FlagAssignment -+mkFlagAssignment = id -+ -+unFlagAssignment :: FlagAssignment -> [(FlagName, Bool)] -+unFlagAssignment = id -+#endif -+ - -- On macOS we're checking whether OpenSSL library is avaiable - -- and if not, we're trying to find Homebrew or MacPorts OpenSSL installations. - -- -@@ -51,7 +65,7 @@ conf descr cfg = do - case c of - Right lbi -> return lbi -- library was found - Left e -- | configConfigurationsFlags cfg -+ | unFlagAssignment (configConfigurationsFlags cfg) - `intersect` [(mkFlagName f, True) | f <- flags] /= [] -> - E.throw e - -- flag was set but library still wasn't found -@@ -86,7 +100,10 @@ multipleFound fs = unlines - , "to specify location of installed OpenSSL library." - ] - --setFlag f c = c { configConfigurationsFlags = go (configConfigurationsFlags c) } -+setFlag f c = c { configConfigurationsFlags = mkFlagAssignment -+ $ go -+ $ unFlagAssignment -+ $ configConfigurationsFlags c } - where go [] = [] - go (x@(n, _):xs) - | n == f = (f, True) : xs - -From 7abc6d490b3914037e6c538b911470303afda111 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue, 23 Jan 2018 21:30:58 -0500 -Subject: [PATCH 2/2] Compat with older Cabals - ---- - Setup.hs | 4 ++-- - 1 file changed, 2 insertions(+), 2 deletions(-) - -diff --git a/Setup.hs b/Setup.hs -index 8f27fde..d7287d1 100755 ---- a/Setup.hs -+++ b/Setup.hs -@@ -19,9 +19,9 @@ import Distribution.PackageDescription (FlagName(..)) - #endif - - #if MIN_VERSION_Cabal(2,1,0) --import Distribution.Types.GenericPackageDescription (mkFlagAssignment, unFlagAssignment) -+import Distribution.PackageDescription (mkFlagAssignment, unFlagAssignment) - #else --import Distribution.Types.GenericPackageDescription (FlagAssignment) -+import Distribution.PackageDescription (FlagAssignment) - #endif - - import Distribution.Verbosity (silent) diff --git a/patches/JuicyPixels-3.2.8.3.patch b/patches/JuicyPixels-3.2.8.3.patch deleted file mode 100644 index 3c74812fe8aeed3bbfe1095df40c1c5d4bccd118..0000000000000000000000000000000000000000 --- a/patches/JuicyPixels-3.2.8.3.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ru JuicyPixels-3.2.8.3.orig/src/Codec/Picture/Metadata.hs JuicyPixels-3.2.8.3/src/Codec/Picture/Metadata.hs ---- JuicyPixels-3.2.8.3.orig/src/Codec/Picture/Metadata.hs 2016-09-04 14:18:57.000000000 +0200 -+++ JuicyPixels-3.2.8.3/src/Codec/Picture/Metadata.hs 2017-09-18 11:42:24.571084437 +0200 -@@ -45,6 +45,7 @@ - import Data.Monoid( Monoid, mempty, mappend ) - import Data.Word( Word ) - #endif -+import Data.Semigroup( Semigroup(..) ) - - - import Control.DeepSeq( NFData( .. ) ) -@@ -168,9 +169,12 @@ - } - deriving (Show, NFData) - -+instance Semigroup Metadatas where -+ (<>) = union -+ - instance Monoid Metadatas where - mempty = empty -- mappend = union -+ mappend = (<>) - - -- | Right based union - union :: Metadatas -> Metadatas -> Metadatas -Only in JuicyPixels-3.2.8.3/src/Codec/Picture: Metadata.hs~ diff --git a/patches/JuicyPixels-3.2.9.1.patch b/patches/JuicyPixels-3.2.9.1.patch deleted file mode 100644 index f54288a18fb617f97311c37014c9395cdf5cc26b..0000000000000000000000000000000000000000 --- a/patches/JuicyPixels-3.2.9.1.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ru JuicyPixels-3.2.9.1/src/Codec/Picture/Metadata.hs JuicyPixels-3.2.9.1-patched/src/Codec/Picture/Metadata.hs ---- JuicyPixels-3.2.9.1/src/Codec/Picture/Metadata.hs 2017-11-11 17:35:34.000000000 +0800 -+++ JuicyPixels-3.2.9.1-patched/src/Codec/Picture/Metadata.hs 2017-12-08 12:22:34.000000000 +0800 -@@ -46,7 +46,7 @@ - import Data.Monoid( Monoid, mempty, mappend ) - import Data.Word( Word ) - #endif -- -+import Data.Semigroup( Semigroup(..) ) - - import Control.DeepSeq( NFData( .. ) ) - import qualified Data.Foldable as F -@@ -169,9 +169,12 @@ - } - deriving (Show, NFData) - -+instance Semigroup Metadatas where -+ (<>) = union -+ - instance Monoid Metadatas where - mempty = empty -- mappend = union -+ mappend = (<>) - - -- | Right based union - union :: Metadatas -> Metadatas -> Metadatas diff --git a/patches/JuicyPixels-3.2.9.2.patch b/patches/JuicyPixels-3.2.9.2.patch deleted file mode 100644 index be8c73d03fc7b3470454895063c122be05bc5594..0000000000000000000000000000000000000000 --- a/patches/JuicyPixels-3.2.9.2.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ru JuicyPixels-3.2.9.2/src/Codec/Picture/Metadata.hs JuicyPixels-3.2.9.2-patched/src/Codec/Picture/Metadata.hs ---- JuicyPixels-3.2.9.2/src/Codec/Picture/Metadata.hs 2017-11-11 17:35:34.000000000 +0800 -+++ JuicyPixels-3.2.9.2-patched/src/Codec/Picture/Metadata.hs 2018-01-10 12:49:40.000000000 +0800 -@@ -46,7 +46,7 @@ - import Data.Monoid( Monoid, mempty, mappend ) - import Data.Word( Word ) - #endif -- -+import Data.Semigroup( Semigroup(..) ) - - import Control.DeepSeq( NFData( .. ) ) - import qualified Data.Foldable as F -@@ -169,9 +169,12 @@ - } - deriving (Show, NFData) - -+instance Semigroup Metadatas where -+ (<>) = union -+ - instance Monoid Metadatas where - mempty = empty -- mappend = union -+ mappend = (<>) - - -- | Right based union - union :: Metadatas -> Metadatas -> Metadatas diff --git a/patches/JuicyPixels-3.2.9.3.patch b/patches/JuicyPixels-3.2.9.3.patch deleted file mode 100644 index e607a2a1f5e4aa6950cf3eb53534a0ab9db50a5a..0000000000000000000000000000000000000000 --- a/patches/JuicyPixels-3.2.9.3.patch +++ /dev/null @@ -1,25 +0,0 @@ -diff -ru JuicyPixels-3.2.9.3.orig/src/Codec/Picture/Metadata.hs JuicyPixels-3.2.9.3/src/Codec/Picture/Metadata.hs ---- JuicyPixels-3.2.9.3.orig/src/Codec/Picture/Metadata.hs 2017-11-11 04:35:34.000000000 -0500 -+++ JuicyPixels-3.2.9.3/src/Codec/Picture/Metadata.hs 2018-01-25 10:20:07.641487188 -0500 -@@ -38,7 +38,7 @@ - - -- * Conversion functions - , dotsPerMeterToDotPerInch -- , dotPerInchToDotsPerMeter -+ , dotPerInchToDotsPerMeter - , dotsPerCentiMeterToDotPerInch - ) where - -@@ -171,7 +171,12 @@ - - instance Monoid Metadatas where - mempty = empty -+#if !MIN_VERSION_base(4,11,0) - mappend = union -+#else -+instance Semigroup Metadatas where -+ (<>) = union -+#endif - - -- | Right based union - union :: Metadatas -> Metadatas -> Metadatas diff --git a/patches/List-0.6.0.patch b/patches/List-0.6.0.patch deleted file mode 100644 index d62fa83a1cacdc823506475d197dcb66efab479e..0000000000000000000000000000000000000000 --- a/patches/List-0.6.0.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ru List-0.6.0.orig/src/Control/Monad/ListT.hs List-0.6.0/src/Control/Monad/ListT.hs ---- List-0.6.0.orig/src/Control/Monad/ListT.hs 2016-10-31 09:42:01.000000000 +0100 -+++ List-0.6.0/src/Control/Monad/ListT.hs 2017-09-17 11:20:22.403495565 +0200 -@@ -30,6 +30,7 @@ - import Control.Monad.IO.Class (MonadIO(..)) - import Control.Monad.Trans.Class (MonadTrans(..)) - import Data.Monoid (Monoid(..)) -+import Data.Semigroup - - newtype ListT m a = - ListT { runListT :: m (ListItem (ListT m) a) } -@@ -46,9 +47,12 @@ - where - step x = return . consFunc x . joinL - -+instance Monad m => Semigroup (ListT m a) where -+ (<>) = flip (foldrL' cons) -+ - instance Monad m => Monoid (ListT m a) where - mempty = ListT $ return Nil -- mappend = flip (foldrL' cons) -+ mappend = (<>) - - instance Monad m => Functor (ListT m) where - fmap func = foldrL' (cons . func) mempty -Only in List-0.6.0/src/Control/Monad: ListT.hs~ diff --git a/patches/MemoTrie-0.6.8.patch b/patches/MemoTrie-0.6.8.patch deleted file mode 100644 index ceb8647665129a2e1ac503f6908b273250458d04..0000000000000000000000000000000000000000 --- a/patches/MemoTrie-0.6.8.patch +++ /dev/null @@ -1,26 +0,0 @@ -From 11f8791c3b29db3351c89cc85faa2dc8068a55ce Mon Sep 17 00:00:00 2001 -From: Kosyrev Serge <serge.kosyrev@iohk.io> -Date: Sat, 13 Jan 2018 19:51:44 +0300 -Subject: [PATCH] Data.Memotrie: Semigroup instane for :->: (GHC 8.4 compat) - ---- - src/Data/MemoTrie.hs | 5 +++++ - 1 file changed, 5 insertions(+) - -diff --git a/src/Data/MemoTrie.hs b/src/Data/MemoTrie.hs -index 8ea692e..fafe16d 100644 ---- a/src/Data/MemoTrie.hs -+++ b/src/Data/MemoTrie.hs -@@ -587,7 +587,12 @@ instance HasTrie a => Monad ((:->:) a) where - - instance (HasTrie a, Monoid b) => Monoid (a :->: b) where - mempty = trie mempty -+#if !MIN_VERSION_base(4,11,0) - mappend = inTrie2 mappend -+#else -+instance (HasTrie a, Semigroup b) => Semigroup (a :->: b) where -+ (<>) = inTrie2 (<>) -+#endif - - instance HasTrie a => Functor ((:->:) a) where - fmap f = inTrie (fmap f) diff --git a/patches/OneTuple-0.2.1.patch b/patches/OneTuple-0.2.1.patch deleted file mode 100644 index 36fa77741dcf4e73b00b7e48052231eb0a3a517b..0000000000000000000000000000000000000000 --- a/patches/OneTuple-0.2.1.patch +++ /dev/null @@ -1,38 +0,0 @@ -diff -ru OneTuple-0.2.1.orig/Data/Tuple/OneTuple.hs OneTuple-0.2.1/Data/Tuple/OneTuple.hs ---- OneTuple-0.2.1.orig/Data/Tuple/OneTuple.hs 2009-03-24 13:25:57.000000000 -0400 -+++ OneTuple-0.2.1/Data/Tuple/OneTuple.hs 2018-01-25 13:37:54.729786042 -0500 -@@ -1,4 +1,4 @@ -- -+{-# LANGUAGE CPP #-} - -- |OneTuple fills the /tuple gap/ with a singleton tuple. - -- - -- OneTuple /does not support/ the usual parenthesized tuple syntax. -@@ -22,6 +22,9 @@ - import Data.Foldable - import Data.Ix - import Data.Monoid -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup (Semigroup(..)) -+#endif - import Data.Traversable - - -- |OneTuple is the singleton tuple data type. -@@ -68,9 +71,18 @@ - (OneTuple x) >>= f = f x - return = OneTuple - -+#if MIN_VERSION_base(4,9,0) -+instance (Semigroup a) => Semigroup (OneTuple a) where -+ OneTuple x <> OneTuple y = OneTuple (x <> y) -+ sconcat = Prelude.foldr1 (<>) -+ stimes n (OneTuple a) = OneTuple (stimes n a) -+#endif -+ - instance (Monoid a) => Monoid (OneTuple a) where - mempty = OneTuple mempty -+#if !(MIN_VERSION_base(4,11,0)) - mappend (OneTuple x) (OneTuple y) = OneTuple (mappend x y) -+#endif - mconcat = Prelude.foldr1 mappend - - instance MonadFix OneTuple where diff --git a/patches/accelerate-1.1.1.0.patch b/patches/accelerate-1.1.1.0.patch deleted file mode 100644 index 79d5b2292378f1bcce9e3136a47a54b7d496f55e..0000000000000000000000000000000000000000 --- a/patches/accelerate-1.1.1.0.patch +++ /dev/null @@ -1,161 +0,0 @@ -diff -ru accelerate-1.1.1.0.orig/Data/Array/Accelerate/Classes/FromIntegral.hs accelerate-1.1.1.0/Data/Array/Accelerate/Classes/FromIntegral.hs ---- accelerate-1.1.1.0.orig/Data/Array/Accelerate/Classes/FromIntegral.hs 2017-09-20 23:08:58.000000000 -0400 -+++ accelerate-1.1.1.0/Data/Array/Accelerate/Classes/FromIntegral.hs 2018-01-23 13:08:52.889390481 -0500 -@@ -61,10 +61,16 @@ - TyConI (DataD _ _ _ _ cons _) <- reify name - #endif - let -+ -- This is what a constructor such as IntegralNumType will be reified -+ -- as prior to GHC 8.4... - dig (NormalC _ [(_, AppT (ConT n) (VarT _))]) = digItOut n - #if __GLASGOW_HASKELL__ < 800 - dig (ForallC _ _ (NormalC _ [(_, AppT (ConT _) (ConT n))])) = return [n] - #else -+ -- ...but this is what IntegralNumType will be reified as on GHC 8.4 -+ -- and later, after the changes described in -+ -- https://ghc.haskell.org/trac/ghc/wiki/Migration/8.4#TemplateHaskellreificationchangesforGADTs -+ dig (ForallC _ _ (GadtC _ [(_, AppT (ConT n) (VarT _))] _)) = digItOut n - dig (GadtC _ _ (AppT (ConT _) (ConT n))) = return [n] - #endif - dig _ = error "Unexpected case generating FromIntegral instances" -diff -ru accelerate-1.1.1.0.orig/Data/Array/Accelerate/Classes/ToFloating.hs accelerate-1.1.1.0/Data/Array/Accelerate/Classes/ToFloating.hs ---- accelerate-1.1.1.0.orig/Data/Array/Accelerate/Classes/ToFloating.hs 2017-05-08 23:19:50.000000000 -0400 -+++ accelerate-1.1.1.0/Data/Array/Accelerate/Classes/ToFloating.hs 2018-01-23 13:07:42.681388713 -0500 -@@ -57,10 +57,16 @@ - TyConI (DataD _ _ _ _ cons _) <- reify name - #endif - let -+ -- This is what a constructor such as IntegralNumType will be reified -+ -- as prior to GHC 8.4... - dig (NormalC _ [(_, AppT (ConT n) (VarT _))]) = digItOut n - #if __GLASGOW_HASKELL__ < 800 - dig (ForallC _ _ (NormalC _ [(_, AppT (ConT _) (ConT n))])) = return [n] - #else -+ -- ...but this is what IntegralNumType will be reified as on GHC 8.4 -+ -- and later, after the changes described in -+ -- https://ghc.haskell.org/trac/ghc/wiki/Migration/8.4#TemplateHaskellreificationchangesforGADTs -+ dig (ForallC _ _ (GadtC _ [(_, AppT (ConT n) (VarT _))] _)) = digItOut n - dig (GadtC _ _ (AppT (ConT _) (ConT n))) = return [n] - #endif - dig _ = error "Unexpected case generating ToFloating instances" -diff -ru accelerate-1.1.1.0.orig/Data/Array/Accelerate/Data/Fold.hs accelerate-1.1.1.0/Data/Array/Accelerate/Data/Fold.hs ---- accelerate-1.1.1.0.orig/Data/Array/Accelerate/Data/Fold.hs 2017-05-08 23:19:50.000000000 -0400 -+++ accelerate-1.1.1.0/Data/Array/Accelerate/Data/Fold.hs 2018-01-23 13:20:48.461408502 -0500 -@@ -78,7 +78,7 @@ - -> Acc (Array sh o) - runFold (Fold tally summarise) is - = A.map summarise -- $ A.fold (<>) mempty -+ $ A.fold mappend mempty - $ A.map tally is - - -diff -ru accelerate-1.1.1.0.orig/Data/Array/Accelerate/Data/Monoid.hs accelerate-1.1.1.0/Data/Array/Accelerate/Data/Monoid.hs ---- accelerate-1.1.1.0.orig/Data/Array/Accelerate/Data/Monoid.hs 2017-07-16 23:17:03.000000000 -0400 -+++ accelerate-1.1.1.0/Data/Array/Accelerate/Data/Monoid.hs 2018-01-23 13:19:27.581406465 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE ConstraintKinds #-} - {-# LANGUAGE FlexibleContexts #-} - {-# LANGUAGE FlexibleInstances #-} -@@ -33,7 +34,12 @@ - import Data.Array.Accelerate.Array.Sugar as A - - import Data.Function --import Data.Monoid hiding ( mconcat ) -+#if __GLASGOW_HASKELL__ >= 800 -+import Data.Monoid hiding ( (<>) ) -+import Data.Semigroup -+#else -+import Data.Monoid -+#endif - import qualified Prelude as P - - -@@ -64,6 +70,13 @@ - mempty = 0 - mappend = lift2 (mappend :: Sum (Exp a) -> Sum (Exp a) -> Sum (Exp a)) - -+#if __GLASGOW_HASKELL__ >= 800 -+-- | @since 1.2.0.0 -+instance Num a => Semigroup (Exp (Sum a)) where -+ (<>) = (+) -+ -- stimes n x = lift . Sum $ n * getSum (unlift x) -+#endif -+ - instance A.Num a => P.Num (Exp (Sum a)) where - (+) = lift2 ((+) :: Sum (Exp a) -> Sum (Exp a) -> Sum (Exp a)) - (-) = lift2 ((-) :: Sum (Exp a) -> Sum (Exp a) -> Sum (Exp a)) -@@ -113,6 +126,13 @@ - mempty = 1 - mappend = lift2 (mappend :: Product (Exp a) -> Product (Exp a) -> Product (Exp a)) - -+#if __GLASGOW_HASKELL__ >= 800 -+-- | @since 1.2.0.0 -+instance Num a => Semigroup (Exp (Product a)) where -+ (<>) = (*) -+ -- stimes n x = lift . Product $ getProduct (unlift x) ^ constant n -+#endif -+ - instance A.Num a => P.Num (Exp (Product a)) where - (+) = lift2 ((+) :: Product (Exp a) -> Product (Exp a) -> Product (Exp a)) - (-) = lift2 ((-) :: Product (Exp a) -> Product (Exp a) -> Product (Exp a)) -@@ -147,26 +167,54 @@ - mappend x y = let (a1,b1) = unlift x :: (Exp a, Exp b) - (a2,b2) = unlift y - in -- lift (a1<>a2, b1<>b2) -+ lift (a1 `mappend` a2, b1 `mappend` b2) - - instance (Elt a, Elt b, Elt c, Monoid (Exp a), Monoid (Exp b), Monoid (Exp c)) => Monoid (Exp (a,b,c)) where - mempty = lift (mempty :: Exp a, mempty :: Exp b, mempty :: Exp c) - mappend x y = let (a1,b1,c1) = unlift x :: (Exp a, Exp b, Exp c) - (a2,b2,c2) = unlift y - in -- lift (a1<>a2, b1<>b2, c1<>c2) -+ lift (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2) - - instance (Elt a, Elt b, Elt c, Elt d, Monoid (Exp a), Monoid (Exp b), Monoid (Exp c), Monoid (Exp d)) => Monoid (Exp (a,b,c,d)) where - mempty = lift (mempty :: Exp a, mempty :: Exp b, mempty :: Exp c, mempty :: Exp d) - mappend x y = let (a1,b1,c1,d1) = unlift x :: (Exp a, Exp b, Exp c, Exp d) - (a2,b2,c2,d2) = unlift y - in -- lift (a1<>a2, b1<>b2, c1<>c2, d1<>d2) -+ lift (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2, d1 `mappend` d2) - - instance (Elt a, Elt b, Elt c, Elt d, Elt e, Monoid (Exp a), Monoid (Exp b), Monoid (Exp c), Monoid (Exp d), Monoid (Exp e)) => Monoid (Exp (a,b,c,d,e)) where - mempty = lift (mempty :: Exp a, mempty :: Exp b, mempty :: Exp c, mempty :: Exp d, mempty :: Exp e) - mappend x y = let (a1,b1,c1,d1,e1) = unlift x :: (Exp a, Exp b, Exp c, Exp d, Exp e) - (a2,b2,c2,d2,e2) = unlift y - in -- lift (a1<>a2, b1<>b2, c1<>c2, d1<>d2, e1<>e2) -+ lift (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2, d1 `mappend` d2, e1 `mappend` e2) -+ -+#if __GLASGOW_HASKELL__ >= 800 -+instance Semigroup (Exp ()) where -+ _ <> _ = constant () -+ -+instance (Elt a, Elt b, Semigroup (Exp a), Semigroup (Exp b)) => Semigroup (Exp (a,b)) where -+ x <> y = let (a1,b1) = unlift x :: (Exp a, Exp b) -+ (a2,b2) = unlift y -+ in -+ lift (a1 <> a2, b1 <> b2) -+ -+instance (Elt a, Elt b, Elt c, Semigroup (Exp a), Semigroup (Exp b), Semigroup (Exp c)) => Semigroup (Exp (a,b,c)) where -+ x <> y = let (a1,b1,c1) = unlift x :: (Exp a, Exp b, Exp c) -+ (a2,b2,c2) = unlift y -+ in -+ lift (a1 <> a2, b1 <> b2, c1 <> c2) - -+instance (Elt a, Elt b, Elt c, Elt d, Semigroup (Exp a), Semigroup (Exp b), Semigroup (Exp c), Semigroup (Exp d)) => Semigroup (Exp (a,b,c,d)) where -+ x <> y = let (a1,b1,c1,d1) = unlift x :: (Exp a, Exp b, Exp c, Exp d) -+ (a2,b2,c2,d2) = unlift y -+ in -+ lift (a1 <> a2, b1 <> b2, c1 <> c2, d1 <> d2) -+ -+instance (Elt a, Elt b, Elt c, Elt d, Elt e, Semigroup (Exp a), Semigroup (Exp b), Semigroup (Exp c), Semigroup (Exp d), Semigroup (Exp e)) => Semigroup (Exp (a,b,c,d,e)) where -+ x <> y = let (a1,b1,c1,d1,e1) = unlift x :: (Exp a, Exp b, Exp c, Exp d, Exp e) -+ (a2,b2,c2,d2,e2) = unlift y -+ in -+ lift (a1 <> a2, b1 <> b2, c1 <> c2, d1 <> d2, e1 <> e2) -+#endif diff --git a/patches/accelerate-1.2.0.0.patch b/patches/accelerate-1.2.0.0.patch deleted file mode 100644 index 668efb645308286da9ecc2ca235df9ba6cd8a371..0000000000000000000000000000000000000000 --- a/patches/accelerate-1.2.0.0.patch +++ /dev/null @@ -1,33 +0,0 @@ -diff -ru accelerate-1.2.0.0.orig/src/Data/Array/Accelerate/Data/Monoid.hs accelerate-1.2.0.0/src/Data/Array/Accelerate/Data/Monoid.hs ---- accelerate-1.2.0.0.orig/src/Data/Array/Accelerate/Data/Monoid.hs 2018-03-20 23:21:17.000000000 -0400 -+++ accelerate-1.2.0.0/src/Data/Array/Accelerate/Data/Monoid.hs 2018-07-04 21:51:33.816351664 -0400 -@@ -5,6 +5,7 @@ - {-# LANGUAGE MultiParamTypeClasses #-} - {-# LANGUAGE ScopedTypeVariables #-} - {-# LANGUAGE TypeFamilies #-} -+{-# LANGUAGE UndecidableInstances #-} - {-# OPTIONS_GHC -fno-warn-orphans #-} - -- | - -- Module : Data.Array.Accelerate.Data.Monoid -diff -ru accelerate-1.2.0.0.orig/src/Data/Array/Accelerate/Data/Semigroup.hs accelerate-1.2.0.0/src/Data/Array/Accelerate/Data/Semigroup.hs ---- accelerate-1.2.0.0.orig/src/Data/Array/Accelerate/Data/Semigroup.hs 2018-03-19 00:08:29.000000000 -0400 -+++ accelerate-1.2.0.0/src/Data/Array/Accelerate/Data/Semigroup.hs 2018-07-04 21:51:12.028351115 -0400 -@@ -5,6 +5,7 @@ - {-# LANGUAGE RebindableSyntax #-} - {-# LANGUAGE ScopedTypeVariables #-} - {-# LANGUAGE TypeFamilies #-} -+{-# LANGUAGE UndecidableInstances #-} - {-# LANGUAGE ViewPatterns #-} - {-# OPTIONS_GHC -fno-warn-orphans #-} - -- | -diff -ru accelerate-1.2.0.0.orig/src/Data/Array/Accelerate/Lift.hs accelerate-1.2.0.0/src/Data/Array/Accelerate/Lift.hs ---- accelerate-1.2.0.0.orig/src/Data/Array/Accelerate/Lift.hs 2018-03-19 00:08:29.000000000 -0400 -+++ accelerate-1.2.0.0/src/Data/Array/Accelerate/Lift.hs 2018-07-04 21:50:26.520349969 -0400 -@@ -4,6 +4,7 @@ - {-# LANGUAGE MultiParamTypeClasses #-} - {-# LANGUAGE TypeFamilies #-} - {-# LANGUAGE TypeOperators #-} -+{-# LANGUAGE UndecidableInstances #-} - #if __GLASGOW_HASKELL__ <= 708 - {-# LANGUAGE OverlappingInstances #-} - {-# OPTIONS_GHC -fno-warn-unrecognised-pragmas #-} diff --git a/patches/accelerate-llvm-1.1.0.0.patch b/patches/accelerate-llvm-1.1.0.0.patch deleted file mode 100644 index 167546cecefec5e49f4a24f83c2653ac3c3271f5..0000000000000000000000000000000000000000 --- a/patches/accelerate-llvm-1.1.0.0.patch +++ /dev/null @@ -1,109 +0,0 @@ -diff -ru accelerate-llvm-1.1.0.0.orig/Control/Parallel/Meta.hs accelerate-llvm-1.1.0.0/Control/Parallel/Meta.hs ---- accelerate-llvm-1.1.0.0.orig/Control/Parallel/Meta.hs 2017-07-03 19:46:40.000000000 -0400 -+++ accelerate-llvm-1.1.0.0/Control/Parallel/Meta.hs 2018-01-23 19:09:25.433935263 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# OPTIONS_HADDOCK hide #-} - -- | - -- Module : Control.Parallel.Meta -@@ -24,7 +25,10 @@ - import Control.Parallel.Meta.Worker - import Data.ByteString.Short ( ShortByteString ) - import Data.Concurrent.Deque.Class --import Data.Monoid -+import Data.Monoid ( Monoid(..) ) -+#if __GLASGOW_HASKELL__ >= 800 -+import Data.Semigroup ( Semigroup(..) ) -+#endif - import Data.Sequence ( Seq ) - import Data.Range.Range as R - import qualified Data.Vector as V -@@ -39,6 +43,11 @@ - data Startup = Startup { - _runStartup :: Gang -> IO () } - -+#if __GLASGOW_HASKELL__ >= 800 -+instance Semigroup Startup where -+ Startup st1 <> Startup st2 = Startup $ \g -> st1 g >> st2 g -+#endif -+ - instance Monoid Startup where - mempty = Startup $ \_ -> return () - Startup st1 `mappend` Startup st2 = Startup $ \g -> st1 g >> st2 g -@@ -52,6 +61,17 @@ - data WorkSearch = WorkSearch { - runWorkSearch :: Int -> Workers -> IO (Maybe Range) } - -+#if __GLASGOW_HASKELL__ >= 800 -+instance Semigroup WorkSearch where -+ {-# INLINE (<>) #-} -+ WorkSearch ws1 <> WorkSearch ws2 = -+ WorkSearch $ \tid st -> do -+ mwork <- ws1 tid st -+ case mwork of -+ Nothing -> ws2 tid st -+ _ -> return mwork -+#endif -+ - instance Monoid WorkSearch where - mempty = WorkSearch $ \_ _ -> return Nothing - WorkSearch ws1 `mappend` WorkSearch ws2 = -@@ -72,9 +92,15 @@ - workSearch :: WorkSearch - } - -+#if __GLASGOW_HASKELL__ >= 800 -+instance Semigroup Resource where -+ {-# INLINE (<>) #-} -+ Resource ws1 <> Resource ws2 = Resource (ws1 <> ws2) -+#endif -+ - instance Monoid Resource where - mempty = Resource mempty -- mappend (Resource ws1) (Resource ws2) = Resource (ws1 <> ws2) -+ mappend (Resource ws1) (Resource ws2) = Resource (ws1 `mappend` ws2) - - - -- | An action to execute. The first parameters are the start and end indices of -@@ -112,6 +138,11 @@ - _runFinalise :: Seq Range -> IO () - } - -+#if __GLASGOW_HASKELL__ >= 800 -+instance Semigroup Finalise where -+ Finalise f1 <> Finalise f2 = Finalise $ \r -> f1 r >> f2 r -+#endif -+ - instance Monoid Finalise where - mempty = Finalise $ \_ -> return () - Finalise f1 `mappend` Finalise f2 = Finalise $ \r -> f1 r >> f2 r -diff -ru accelerate-llvm-1.1.0.0.orig/LLVM/AST/Type/Name.hs accelerate-llvm-1.1.0.0/LLVM/AST/Type/Name.hs ---- accelerate-llvm-1.1.0.0.orig/LLVM/AST/Type/Name.hs 2017-08-25 03:09:47.000000000 -0400 -+++ accelerate-llvm-1.1.0.0/LLVM/AST/Type/Name.hs 2018-01-23 19:00:51.009922308 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DeriveDataTypeable #-} - {-# LANGUAGE RoleAnnotations #-} - {-# OPTIONS_HADDOCK hide #-} -@@ -16,6 +17,9 @@ - - import Data.ByteString.Short ( ShortByteString ) - import Data.Data -+#if __GLASGOW_HASKELL__ >= 800 -+import Data.Semigroup -+#endif - import Data.String - import Data.Word - import Prelude -@@ -71,6 +75,11 @@ - instance IsString Label where - fromString = Label . fromString - -+#if __GLASGOW_HASKELL__ >= 800 -+instance Semigroup Label where -+ Label x <> Label y = Label (x <> y) -+#endif -+ - instance Monoid Label where - mempty = Label mempty - mappend (Label x) (Label y) = Label (mappend x y) diff --git a/patches/accelerate-llvm-native-1.1.0.1.patch b/patches/accelerate-llvm-native-1.1.0.1.patch deleted file mode 100644 index 27643027dc654e901228e44a5e5c3ba4c5950115..0000000000000000000000000000000000000000 --- a/patches/accelerate-llvm-native-1.1.0.1.patch +++ /dev/null @@ -1,57 +0,0 @@ -diff --git a/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC.hs b/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC.hs -index 31fa503a..8766276d 100644 ---- a/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC.hs -+++ b/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC.hs -@@ -30,7 +30,6 @@ import Distribution.Simple.Utils - import qualified Distribution.ModuleName as ModuleName - import Distribution.Simple.Program - import qualified Distribution.Simple.Program.Ar as Ar --import qualified Distribution.Simple.Program.Ld as Ld - import Distribution.Simple.Program.GHC - import Distribution.Simple.Setup - import qualified Distribution.Simple.Setup as Cabal -@@ -359,7 +358,7 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do - - whenGHCiLib $ do - (ldProg, _) <- requireProgram verbosity ldProgram (withPrograms lbi) -- Ld.combineObjectFiles verbosity ldProg -+ Internal.combineObjectFiles verbosity lbi ldProg - ghciLibFilePath ghciObjFiles - - whenSharedLib False $ -diff --git a/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC/Internal.hs b/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC/Internal.hs -index e7e2f953..47a879af 100644 ---- a/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC/Internal.hs -+++ b/Data/Array/Accelerate/LLVM/Native/Distribution/Simple/GHC/Internal.hs -@@ -19,6 +19,7 @@ module Data.Array.Accelerate.LLVM.Native.Distribution.Simple.GHC.Internal ( - getHaskellObjects, - mkGhcOptPackages, - profDetailLevelFlag, -+ combineObjectFiles - - ) where - -@@ -28,9 +29,12 @@ import Distribution.Backpack - import Distribution.PackageDescription as PD hiding (Flag) - import Distribution.Simple.Compiler hiding (Flag) - import Distribution.Simple.LocalBuildInfo -+import Distribution.Simple.Program (ConfiguredProgram) - import Distribution.Simple.Program.GHC -+import qualified Distribution.Simple.Program.Ld as Ld - import Distribution.Simple.Setup - import Distribution.Simple -+import Distribution.Verbosity (Verbosity) - import qualified Distribution.ModuleName as ModuleName - - import qualified Data.Map as Map -@@ -113,3 +117,10 @@ allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName.ModuleName] - allLibModules lib _ = libModules lib - #endif - -+combineObjectFiles :: Verbosity -> LocalBuildInfo -> ConfiguredProgram -+ -> FilePath -> [FilePath] -> IO () -+#if MIN_VERSION_Cabal(2,1,0) -+combineObjectFiles = Ld.combineObjectFiles -+#else -+combineObjectFiles v _ = Ld.combineObjectFiles v -+#endif diff --git a/patches/basement-0.0.2.patch b/patches/basement-0.0.2.patch deleted file mode 100644 index 90c6d955626d2fd3063c941365a8d07c2598be4b..0000000000000000000000000000000000000000 --- a/patches/basement-0.0.2.patch +++ /dev/null @@ -1,139 +0,0 @@ -diff -ru basement-0.0.2.orig/Basement/Block/Base.hs basement-0.0.2/Basement/Block/Base.hs ---- basement-0.0.2.orig/Basement/Block/Base.hs 2017-08-05 12:49:52.000000000 +0200 -+++ basement-0.0.2/Basement/Block/Base.hs 2017-09-15 11:58:10.129571964 +0200 -@@ -40,6 +40,7 @@ - import Basement.NormalForm - import Basement.Numerical.Additive - import Basement.PrimType -+import Data.Semigroup - - -- | A block of memory containing unpacked bytes representing values of type 'ty' - data Block ty = Block ByteArray# -@@ -63,9 +64,12 @@ - instance (PrimType ty, Ord ty) => Ord (Block ty) where - compare = internalCompare - -+instance PrimType ty => Semigroup (Block ty) where -+ (<>) = append -+ - instance PrimType ty => Monoid (Block ty) where - mempty = empty -- mappend = append -+ mappend = (<>) - mconcat = concat - - instance PrimType ty => IsList (Block ty) where -Only in basement-0.0.2/Basement/Block: Base.hs~ -diff -ru basement-0.0.2.orig/Basement/BoxedArray.hs basement-0.0.2/Basement/BoxedArray.hs ---- basement-0.0.2.orig/Basement/BoxedArray.hs 2017-09-03 10:51:08.000000000 +0200 -+++ basement-0.0.2/Basement/BoxedArray.hs 2017-09-15 11:59:29.993121551 +0200 -@@ -89,6 +89,7 @@ - import Basement.Exception - import Basement.MutableBuilder - import qualified Basement.Compat.ExtList as List -+import Data.Semigroup - - -- | Array of a - data Array a = Array {-# UNPACK #-} !(Offset a) -@@ -121,9 +122,12 @@ - instance Functor Array where - fmap = map - -+instance Semigroup (Array a) where -+ (<>) = append -+ - instance Monoid (Array a) where - mempty = empty -- mappend = append -+ mappend = (<>) - mconcat = concat - - instance Show a => Show (Array a) where -Only in basement-0.0.2/Basement: BoxedArray.hs~ -diff -ru basement-0.0.2.orig/Basement/Types/AsciiString.hs basement-0.0.2/Basement/Types/AsciiString.hs ---- basement-0.0.2.orig/Basement/Types/AsciiString.hs 2017-08-31 18:47:35.000000000 +0200 -+++ basement-0.0.2/Basement/Types/AsciiString.hs 2017-09-15 11:59:50.401006434 +0200 -@@ -26,10 +26,11 @@ - import Basement.UArray.Base - import qualified Basement.Types.Char7 as Char7 - import qualified Basement.UArray as A (all, unsafeRecast) -+import Data.Semigroup - - -- | Opaque packed array of characters in the ASCII encoding - newtype AsciiString = AsciiString { toBytes :: UArray Char7 } -- deriving (Typeable, Monoid, Eq, Ord) -+ deriving (Typeable, Semigroup, Monoid, Eq, Ord) - - newtype MutableAsciiString st = MutableAsciiString (MUArray Char7 st) - deriving (Typeable) -Only in basement-0.0.2/Basement/Types: AsciiString.hs~ -diff -ru basement-0.0.2.orig/Basement/Types/OffsetSize.hs basement-0.0.2/Basement/Types/OffsetSize.hs ---- basement-0.0.2.orig/Basement/Types/OffsetSize.hs 2017-09-03 10:51:08.000000000 +0200 -+++ basement-0.0.2/Basement/Types/OffsetSize.hs 2017-09-15 11:57:22.061842997 +0200 -@@ -55,6 +55,7 @@ - import Basement.IntegralConv - import Data.List (foldl') - import qualified Prelude -+import Data.Semigroup - - #if WORD_SIZE_IN_BITS < 64 - import GHC.IntWord64 -@@ -193,9 +194,12 @@ - (CountOf a) - (CountOf b) | a >= b = Just . CountOf $ a - b - | otherwise = Nothing - -+instance Semigroup (CountOf ty) where -+ (<>) = (+) -+ - instance Monoid (CountOf ty) where - mempty = azero -- mappend = (+) -+ mappend = (<>) - mconcat = foldl' (+) 0 - - instance IntegralCast Int (CountOf ty) where -Only in basement-0.0.2/Basement/Types: OffsetSize.hs~ -diff -ru basement-0.0.2.orig/Basement/UArray/Base.hs basement-0.0.2/Basement/UArray/Base.hs ---- basement-0.0.2.orig/Basement/UArray/Base.hs 2017-09-08 08:03:42.000000000 +0200 -+++ basement-0.0.2/Basement/UArray/Base.hs 2017-09-15 11:58:58.345300054 +0200 -@@ -72,6 +72,7 @@ - import Basement.Bindings.Memory - import Foreign.C.Types - import System.IO.Unsafe (unsafeDupablePerformIO) -+import Data.Semigroup - - -- | A Mutable array of types built on top of GHC primitive. - -- -@@ -114,9 +115,12 @@ - {-# SPECIALIZE instance Ord (UArray Word8) #-} - compare = vCompare - -+instance PrimType ty => Semigroup (UArray ty) where -+ (<>) = append -+ - instance PrimType ty => Monoid (UArray ty) where - mempty = empty -- mappend = append -+ mappend = (<>) - mconcat = concat - - instance PrimType ty => IsList (UArray ty) where -Only in basement-0.0.2/Basement/UArray: Base.hs~ -diff -ru basement-0.0.2.orig/Basement/UTF8/Base.hs basement-0.0.2/Basement/UTF8/Base.hs ---- basement-0.0.2.orig/Basement/UTF8/Base.hs 2017-09-08 08:03:42.000000000 +0200 -+++ basement-0.0.2/Basement/UTF8/Base.hs 2017-09-15 12:00:02.536937977 +0200 -@@ -41,11 +41,12 @@ - import GHC.CString (unpackCString#, unpackCStringUtf8#) - - import Data.Data -+import Data.Semigroup - import Basement.Compat.ExtList as List - - -- | Opaque packed array of characters in the UTF8 encoding - newtype String = String (UArray Word8) -- deriving (Typeable, Monoid, Eq, Ord) -+ deriving (Typeable, Semigroup, Monoid, Eq, Ord) - - -- | Mutable String Buffer. - -- -Only in basement-0.0.2/Basement/UTF8: Base.hs~ diff --git a/patches/basement-0.0.7.patch b/patches/basement-0.0.7.patch deleted file mode 100644 index 164d97096670af853527d11db9e42e73fd2be1fc..0000000000000000000000000000000000000000 --- a/patches/basement-0.0.7.patch +++ /dev/null @@ -1,34 +0,0 @@ -diff -ru basement-0.0.7.orig/Basement/Nat.hs basement-0.0.7/Basement/Nat.hs ---- basement-0.0.7.orig/Basement/Nat.hs 2017-11-11 04:52:31.000000000 -0500 -+++ basement-0.0.7/Basement/Nat.hs 2018-06-24 17:54:55.038235612 -0400 -@@ -8,6 +8,9 @@ - {-# LANGUAGE ScopedTypeVariables #-} - {-# LANGUAGE UndecidableInstances #-} - {-# LANGUAGE ConstraintKinds #-} -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - module Basement.Nat - ( Nat - , KnownNat -diff -ru basement-0.0.7.orig/Basement/Sized/Block.hs basement-0.0.7/Basement/Sized/Block.hs ---- basement-0.0.7.orig/Basement/Sized/Block.hs 2018-02-12 09:24:12.000000000 -0500 -+++ basement-0.0.7/Basement/Sized/Block.hs 2018-06-24 17:56:02.506237311 -0400 -@@ -5,13 +5,16 @@ - -- - -- A Nat-sized version of Block - {-# LANGUAGE AllowAmbiguousTypes #-} -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DataKinds #-} - {-# LANGUAGE TypeOperators #-} - {-# LANGUAGE TypeApplications #-} - {-# LANGUAGE ScopedTypeVariables #-} - {-# LANGUAGE GeneralizedNewtypeDeriving #-} - {-# LANGUAGE ConstraintKinds #-} -- -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - module Basement.Sized.Block - ( BlockN - , MutableBlockN diff --git a/patches/blaze-builder-0.4.0.2.patch b/patches/blaze-builder-0.4.0.2.patch deleted file mode 100644 index e4e3a6fe4b6681910500ec3232138c2fecdbbdee..0000000000000000000000000000000000000000 --- a/patches/blaze-builder-0.4.0.2.patch +++ /dev/null @@ -1,49 +0,0 @@ -diff -ru blaze-builder-0.4.0.2.orig/Blaze/ByteString/Builder/Internal/Write.hs blaze-builder-0.4.0.2/Blaze/ByteString/Builder/Internal/Write.hs ---- blaze-builder-0.4.0.2.orig/Blaze/ByteString/Builder/Internal/Write.hs 2016-04-18 21:47:02.000000000 +0200 -+++ blaze-builder-0.4.0.2/Blaze/ByteString/Builder/Internal/Write.hs 2017-09-14 22:57:46.824329914 +0200 -@@ -56,6 +56,9 @@ - #if !MIN_VERSION_base(4,8,0) - import Data.Monoid - #endif -+#if !MIN_VERSION_base(4,11,0) -+import Data.Semigroup -+#endif - - ------------------------------------------------------------------------------ - -- Poking a buffer and writing to a buffer -@@ -119,23 +122,31 @@ - getBound $ write $ error $ - "getBound' called from " ++ msg ++ ": write bound is not data-independent." - -+instance Semigroup Poke where -+ {-# INLINE (<>) #-} -+ (Poke po1) <> (Poke po2) = Poke $ po1 >=> po2 -+ - instance Monoid Poke where - {-# INLINE mempty #-} - mempty = Poke $ return - - {-# INLINE mappend #-} -- (Poke po1) `mappend` (Poke po2) = Poke $ po1 >=> po2 -+ mappend = (<>) - - {-# INLINE mconcat #-} - mconcat = foldr mappend mempty - -+instance Semigroup Write where -+ {-# INLINE (<>) #-} -+ (Write bound1 w1) <> (Write bound2 w2) = -+ Write (bound1 + bound2) (w1 `mappend` w2) -+ - instance Monoid Write where - {-# INLINE mempty #-} - mempty = Write 0 mempty - - {-# INLINE mappend #-} -- (Write bound1 w1) `mappend` (Write bound2 w2) = -- Write (bound1 + bound2) (w1 `mappend` w2) -+ mappend = (<>) - - {-# INLINE mconcat #-} - mconcat = foldr mappend mempty -Only in blaze-builder-0.4.0.2/Blaze/ByteString/Builder/Internal: Write.hs~ diff --git a/patches/blaze-markup-0.8.0.0.patch b/patches/blaze-markup-0.8.0.0.patch deleted file mode 100644 index a50f88792eee4ab51dbcae36aa1c4a9ce3a826c3..0000000000000000000000000000000000000000 --- a/patches/blaze-markup-0.8.0.0.patch +++ /dev/null @@ -1,79 +0,0 @@ -diff -ru blaze-markup-0.8.0.0.orig/src/Text/Blaze/Internal.hs blaze-markup-0.8.0.0/src/Text/Blaze/Internal.hs ---- blaze-markup-0.8.0.0.orig/src/Text/Blaze/Internal.hs 2017-01-30 17:48:00.000000000 +0100 -+++ blaze-markup-0.8.0.0/src/Text/Blaze/Internal.hs 2017-09-17 11:21:22.831142651 +0200 -@@ -96,7 +96,7 @@ - import GHC.Exts (IsString (..)) - - #if MIN_VERSION_base(4,9,0) --import Data.Semigroup (Semigroup) -+import Data.Semigroup (Semigroup(..)) - #endif - - -- | A static string that supports efficient output to all possible backends. -@@ -134,11 +134,19 @@ - -- | Empty string - | EmptyChoiceString - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup ChoiceString where -+ (<>) = AppendChoiceString -+ {-# INLINE (<>) #-} -+#endif -+ - instance Monoid ChoiceString where - mempty = EmptyChoiceString - {-# INLINE mempty #-} -+#if !(MIN_VERSION_base(4,11,0)) - mappend = AppendChoiceString - {-# INLINE mappend #-} -+#endif - - instance IsString ChoiceString where - fromString = String -@@ -178,13 +186,19 @@ - instance Monoid a => Monoid (MarkupM a) where - mempty = Empty mempty - {-# INLINE mempty #-} -+#if !(MIN_VERSION_base(4,11,0)) - mappend x y = Append x y - {-# INLINE mappend #-} - mconcat = foldr Append (Empty mempty) - {-# INLINE mconcat #-} -+#endif - - #if MIN_VERSION_base(4,9,0) - instance Monoid a => Semigroup (MarkupM a) where -+ x <> y = Append x y -+ {-# INLINE (<>) #-} -+ sconcat = foldr Append (Empty mempty) -+ {-# INLINE sconcat #-} - #endif - - instance Functor MarkupM where -@@ -242,14 +256,25 @@ - -- - newtype Attribute = Attribute (forall a. MarkupM a -> MarkupM a) - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup Attribute where -+ Attribute f <> Attribute g = Attribute (g . f) -+#endif -+ - instance Monoid Attribute where - mempty = Attribute id -+#if !(MIN_VERSION_base(4,11,0)) - Attribute f `mappend` Attribute g = Attribute (g . f) -+#endif - - -- | The type for the value part of an attribute. - -- - newtype AttributeValue = AttributeValue { unAttributeValue :: ChoiceString } -- deriving (IsString, Monoid) -+ deriving (IsString, Monoid -+#if MIN_VERSION_base(4,9,0) -+ ,Semigroup -+#endif -+ ) - - -- | Create a custom parent element - customParent :: Tag -- ^ Element tag diff --git a/patches/boxes-0.1.4.patch b/patches/boxes-0.1.4.patch deleted file mode 100644 index 6b144f8971fbb9c3c5a8582233bf7ffb75b0b1cb..0000000000000000000000000000000000000000 --- a/patches/boxes-0.1.4.patch +++ /dev/null @@ -1,28 +0,0 @@ -diff -ru boxes-0.1.4.orig/Text/PrettyPrint/Boxes.hs boxes-0.1.4/Text/PrettyPrint/Boxes.hs ---- boxes-0.1.4.orig/Text/PrettyPrint/Boxes.hs 2015-01-14 11:19:44.000000000 -0500 -+++ boxes-0.1.4/Text/PrettyPrint/Boxes.hs 2018-01-23 19:44:46.961988690 -0500 -@@ -97,7 +97,9 @@ - - ) where - --#if MIN_VERSION_base(4,8,0) -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ( (<>), Word ) -+#elif MIN_VERSION_base(4,8,0) - import Prelude hiding (Word) - #endif - -diff -ru boxes-0.1.4.orig/Text/PrettyPrint/Tests.hs boxes-0.1.4/Text/PrettyPrint/Tests.hs ---- boxes-0.1.4.orig/Text/PrettyPrint/Tests.hs 2015-01-14 11:19:44.000000000 -0500 -+++ boxes-0.1.4/Text/PrettyPrint/Tests.hs 2018-01-23 19:45:09.913989268 -0500 -@@ -4,6 +4,10 @@ - import Control.Monad - import System.Exit (exitFailure, exitSuccess) - -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ((<>)) -+#endif -+ - instance Arbitrary Alignment where - arbitrary = elements [ AlignFirst - , AlignCenter1 diff --git a/patches/cereal-0.5.4.0.patch b/patches/cereal-0.5.4.0.patch deleted file mode 100644 index b1467141bd0b6bb201e0e303e4a1069d86f70252..0000000000000000000000000000000000000000 --- a/patches/cereal-0.5.4.0.patch +++ /dev/null @@ -1,32 +0,0 @@ -diff -ru cereal-0.5.4.0.orig/src/Data/Serialize/Put.hs cereal-0.5.4.0/src/Data/Serialize/Put.hs ---- cereal-0.5.4.0.orig/src/Data/Serialize/Put.hs 2016-11-09 01:40:53.000000000 +0100 -+++ cereal-0.5.4.0/src/Data/Serialize/Put.hs 2017-09-15 11:28:52.023473444 +0200 -@@ -116,6 +116,10 @@ - import Data.Monoid - #endif - -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif -+ - #if !(MIN_VERSION_bytestring(0,10,0)) - import Foreign.ForeignPtr (withForeignPtr) - import Foreign.Marshal.Utils (copyBytes) -@@ -175,11 +179,15 @@ - (>>) = (*>) - {-# INLINE (>>) #-} - -+instance Semigroup (PutM ()) where -+ (<>) = (*>) -+ {-# INLINE (<>) #-} -+ - instance Monoid (PutM ()) where - mempty = pure () - {-# INLINE mempty #-} - -- mappend = (*>) -+ mappend = (<>) - {-# INLINE mappend #-} - - tell :: Putter Builder -Only in cereal-0.5.4.0/src/Data/Serialize: Put.hs~ diff --git a/patches/cipher-aes128-0.7.0.3.patch b/patches/cipher-aes128-0.7.0.3.patch deleted file mode 100644 index a5d056e71c94c4bd188d9bbc956ad2c6a2ef7160..0000000000000000000000000000000000000000 --- a/patches/cipher-aes128-0.7.0.3.patch +++ /dev/null @@ -1,16 +0,0 @@ -diff -ru cipher-aes128-0.7.0.3.orig/Setup.hs cipher-aes128-0.7.0.3/Setup.hs ---- cipher-aes128-0.7.0.3.orig/Setup.hs 2016-08-31 01:58:48.000000000 -0400 -+++ cipher-aes128-0.7.0.3/Setup.hs 2018-07-04 22:06:10.880373751 -0400 -@@ -13,10 +13,8 @@ - main = defaultMainWithHooks hk - where - hk = simpleUserHooks { buildHook = \pd lbi uh bf -> do -- let ccProg = Program "gcc" undefined undefined undefined -- hcProg = Program "ghc" undefined undefined undefined -- mConf = lookupProgram ccProg (withPrograms lbi) -- hcConf = lookupProgram hcProg (withPrograms lbi) -+ let mConf = lookupProgram gccProgram (withPrograms lbi) -+ hcConf = lookupProgram ghcProgram (withPrograms lbi) - err = error "Could not determine C compiler" - _cc = locationPath . programLocation . maybe err id $ mConf - hc = locationPath . programLocation . maybe err id $ hcConf diff --git a/patches/colour-2.3.3.patch b/patches/colour-2.3.3.patch deleted file mode 100644 index ec4d4334b8d1042459faa13ec9a61a5b7a10d1c9..0000000000000000000000000000000000000000 --- a/patches/colour-2.3.3.patch +++ /dev/null @@ -1,84 +0,0 @@ -diff -ru colour-2.3.3.orig/colour.cabal colour-2.3.3/colour.cabal ---- colour-2.3.3.orig/colour.cabal 2012-01-17 16:49:47.000000000 +0100 -+++ colour-2.3.3/colour.cabal 2017-11-22 19:24:01.955200024 +0100 -@@ -18,7 +18,7 @@ - data-files: README CHANGELOG - - Library -- Build-Depends: base >= 3 && < 5 -+ Build-Depends: base >= 4.9 && < 5 - Exposed-Modules: Data.Colour - Data.Colour.SRGB - Data.Colour.SRGB.Linear -diff -ru colour-2.3.3.orig/Data/Colour/Internal.hs colour-2.3.3/Data/Colour/Internal.hs ---- colour-2.3.3.orig/Data/Colour/Internal.hs 2012-01-17 16:49:47.000000000 +0100 -+++ colour-2.3.3/Data/Colour/Internal.hs 2017-11-22 19:24:01.955200024 +0100 -@@ -25,7 +25,7 @@ - import Data.List - import qualified Data.Colour.Chan as Chan - import Data.Colour.Chan (Chan(Chan)) --import Data.Monoid -+import Data.Semigroup - - data Red = Red - data Green = Green -@@ -53,10 +53,14 @@ - black :: (Num a) => Colour a - black = RGB Chan.empty Chan.empty Chan.empty - -+instance (Num a) => Semigroup (Colour a) where -+ (RGB r1 g1 b1) <> (RGB r2 g2 b2) = -+ RGB (r1 `Chan.add` r2) (g1 `Chan.add` g2) (b1 `Chan.add` b2) -+ -+ - instance (Num a) => Monoid (Colour a) where - mempty = black -- (RGB r1 g1 b1) `mappend` (RGB r2 g2 b2) = -- RGB (r1 `Chan.add` r2) (g1 `Chan.add` g2) (b1 `Chan.add` b2) -+ mappend = (<>) - mconcat l = RGB (Chan.sum lr) (Chan.sum lg) (Chan.sum lb) - where - (lr,lg,lb) = unzip3 (map toRGB l) -@@ -167,10 +171,13 @@ - RGBA (c0 `over` c1) (Chan.over a0 a0' a1) - darken s (RGBA c a) = RGBA (darken s c) a - -+instance (Num a) => Semigroup (AlphaColour a) where -+ (<>) = over -+ - -- | 'AlphaColour' forms a monoid with 'over' and 'transparent'. - instance (Num a) => Monoid (AlphaColour a) where - mempty = transparent -- mappend = over -+ mappend = (<>) - - -- | @c1 \`atop\` c2@ returns the 'AlphaColour' produced by covering - -- the portion of @c2@ visible by @c1@. -diff -ru colour-2.3.3.orig/Data/Colour/RGBSpace.hs colour-2.3.3/Data/Colour/RGBSpace.hs ---- colour-2.3.3.orig/Data/Colour/RGBSpace.hs 2012-01-17 16:49:47.000000000 +0100 -+++ colour-2.3.3/Data/Colour/RGBSpace.hs 2017-11-22 19:24:01.955200024 +0100 -@@ -46,7 +46,7 @@ - ) - where - --import Data.Monoid -+import Data.Semigroup - import Data.Colour.CIE.Chromaticity - import Data.Colour.Matrix - import Data.Colour.RGB -@@ -109,10 +109,13 @@ - inverseTransferFunction (TransferFunction for rev g) = - TransferFunction rev for (recip g) - -+instance (Num a) => Semigroup (TransferFunction a) where -+ (TransferFunction f0 f1 f) <> (TransferFunction g0 g1 g) = -+ (TransferFunction (f0 . g0) (g1 . f1) (f*g)) -+ - instance (Num a) => Monoid (TransferFunction a) where - mempty = linearTransferFunction -- (TransferFunction f0 f1 f) `mappend` (TransferFunction g0 g1 g) = -- (TransferFunction (f0 . g0) (g1 . f1) (f*g)) -+ mappend = (<>) - - -- |An 'RGBSpace' is a colour coordinate system for colours laying - -- 'inGamut' of 'gamut'. diff --git a/patches/conduit-1.2.12.1.patch b/patches/conduit-1.2.12.1.patch deleted file mode 100644 index 859a6c5731a0695c32088d2820569f3f13a852aa..0000000000000000000000000000000000000000 --- a/patches/conduit-1.2.12.1.patch +++ /dev/null @@ -1,107 +0,0 @@ -diff -ru conduit-1.2.12.1.orig/conduit.cabal conduit-1.2.12.1/conduit.cabal ---- conduit-1.2.12.1.orig/conduit.cabal 2018-01-06 17:22:28.828784258 -0500 -+++ conduit-1.2.12.1/conduit.cabal 2018-01-06 17:26:05.524789715 -0500 -@@ -37,6 +37,7 @@ - , resourcet >= 1.1 && < 1.2 - , exceptions >= 0.6 - , lifted-base >= 0.1 -+ , semigroups >= 0.16 - , transformers-base >= 0.4.1 && < 0.5 - , transformers >= 0.2.2 - , transformers-compat >= 0.3 -@@ -60,6 +61,7 @@ - , base - , hspec >= 1.3 - , QuickCheck >= 2.7 -+ , semigroups >= 0.16 - , transformers - , mtl - , resourcet -diff -ru conduit-1.2.12.1.orig/Data/Conduit/Internal/Conduit.hs conduit-1.2.12.1/Data/Conduit/Internal/Conduit.hs ---- conduit-1.2.12.1.orig/Data/Conduit/Internal/Conduit.hs 2017-09-25 03:19:47.000000000 -0400 -+++ conduit-1.2.12.1/Data/Conduit/Internal/Conduit.hs 2018-01-06 17:27:20.360791600 -0500 -@@ -102,6 +102,7 @@ - import Control.Monad.Primitive (PrimMonad, PrimState, primitive) - import Data.Void (Void, absurd) - import Data.Monoid (Monoid (mappend, mempty)) -+import Data.Semigroup (Semigroup ((<>))) - import Control.Monad.Trans.Resource - import qualified Data.IORef as I - import Control.Monad.Morph (MFunctor (..)) -@@ -251,11 +252,17 @@ - liftResourceT = lift . liftResourceT - {-# INLINE liftResourceT #-} - -+instance Monad m => Semigroup (ConduitM i o m ()) where -+ (<>) = (>>) -+ {-# INLINE (<>) #-} -+ - instance Monad m => Monoid (ConduitM i o m ()) where - mempty = return () - {-# INLINE mempty #-} -- mappend = (>>) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) - {-# INLINE mappend #-} -+#endif - - instance PrimMonad m => PrimMonad (ConduitM i o m) where - type PrimState (ConduitM i o m) = PrimState m -diff -ru conduit-1.2.12.1.orig/Data/Conduit/Internal/Pipe.hs conduit-1.2.12.1/Data/Conduit/Internal/Pipe.hs ---- conduit-1.2.12.1.orig/Data/Conduit/Internal/Pipe.hs 2017-04-19 09:32:04.000000000 -0400 -+++ conduit-1.2.12.1/Data/Conduit/Internal/Pipe.hs 2018-01-06 17:28:42.592793670 -0500 -@@ -59,6 +59,7 @@ - import Control.Monad.Primitive (PrimMonad, PrimState, primitive) - import Data.Void (Void, absurd) - import Data.Monoid (Monoid (mappend, mempty)) -+import Data.Semigroup (Semigroup ((<>))) - import Control.Monad.Trans.Resource - import qualified GHC.Exts - import Control.Monad.Morph (MFunctor (..)) -@@ -151,11 +152,17 @@ - go (HaveOutput p c o) = HaveOutput (go p) c o - {-# INLINE catch #-} - -+instance Monad m => Semigroup (Pipe l i o u m ()) where -+ (<>) = (>>) -+ {-# INLINE (<>) #-} -+ - instance Monad m => Monoid (Pipe l i o u m ()) where - mempty = return () - {-# INLINE mempty #-} -- mappend = (>>) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) - {-# INLINE mappend #-} -+#endif - - instance PrimMonad m => PrimMonad (Pipe l i o u m) where - type PrimState (Pipe l i o u m) = PrimState m -Only in conduit-1.2.12.1: .ghc.environment.x86_64-linux-8.4.0.20171222 -diff -ru conduit-1.2.12.1.orig/test/Data/Conduit/StreamSpec.hs conduit-1.2.12.1/test/Data/Conduit/StreamSpec.hs ---- conduit-1.2.12.1.orig/test/Data/Conduit/StreamSpec.hs 2015-11-08 21:09:15.000000000 -0500 -+++ conduit-1.2.12.1/test/Data/Conduit/StreamSpec.hs 2018-01-06 17:30:27.112796303 -0500 -@@ -19,6 +19,7 @@ - import qualified Data.List - import qualified Data.Maybe - import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Prelude - ((.), ($), (>>=), (=<<), return, (==), Int, id, Maybe(..), Monad, - Eq, Show, String, Functor, fst, snd) -@@ -502,9 +503,14 @@ - newtype Sum a = Sum a - deriving (Eq, Show, Arbitrary) - -+instance Prelude.Num a => Semigroup (Sum a) where -+ Sum x <> Sum y = Sum $ x Prelude.+ y -+ - instance Prelude.Num a => Monoid (Sum a) where - mempty = Sum 0 -- mappend (Sum x) (Sum y) = Sum $ x Prelude.+ y -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - preventFusion :: a -> a - preventFusion = id diff --git a/patches/conduit-1.2.12.patch b/patches/conduit-1.2.12.patch deleted file mode 100644 index 3c4bff4224ac2e3b7282e10ec8fcce7935c591e2..0000000000000000000000000000000000000000 --- a/patches/conduit-1.2.12.patch +++ /dev/null @@ -1,66 +0,0 @@ -diff -ru conduit-1.2.12.orig/Data/Conduit/Internal/Conduit.hs conduit-1.2.12/Data/Conduit/Internal/Conduit.hs ---- conduit-1.2.12.orig/Data/Conduit/Internal/Conduit.hs 2017-05-19 18:38:16.000000000 +0200 -+++ conduit-1.2.12/Data/Conduit/Internal/Conduit.hs 2017-09-17 10:47:51.382511075 +0200 -@@ -102,6 +102,9 @@ - import Control.Monad.Primitive (PrimMonad, PrimState, primitive) - import Data.Void (Void, absurd) - import Data.Monoid (Monoid (mappend, mempty)) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Control.Monad.Trans.Resource - import qualified Data.IORef as I - import Control.Monad.Morph (MFunctor (..)) -@@ -247,11 +250,19 @@ - liftResourceT = lift . liftResourceT - {-# INLINE liftResourceT #-} - -+#if MIN_VERSION_base(4,9,0) -+instance Monad m => Semigroup (ConduitM i o m ()) where -+ (<>) = (>>) -+ {-# INLINE (<>) #-} -+#endif -+ - instance Monad m => Monoid (ConduitM i o m ()) where - mempty = return () - {-# INLINE mempty #-} -+#if !(MIN_VERSION_base(4,11,0)) - mappend = (>>) - {-# INLINE mappend #-} -+#endif - - instance PrimMonad m => PrimMonad (ConduitM i o m) where - type PrimState (ConduitM i o m) = PrimState m -diff -ru conduit-1.2.12.orig/Data/Conduit/Internal/Pipe.hs conduit-1.2.12/Data/Conduit/Internal/Pipe.hs ---- conduit-1.2.12.orig/Data/Conduit/Internal/Pipe.hs 2017-04-19 15:32:04.000000000 +0200 -+++ conduit-1.2.12/Data/Conduit/Internal/Pipe.hs 2017-09-17 10:47:51.382511075 +0200 -@@ -59,6 +59,9 @@ - import Control.Monad.Primitive (PrimMonad, PrimState, primitive) - import Data.Void (Void, absurd) - import Data.Monoid (Monoid (mappend, mempty)) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Control.Monad.Trans.Resource - import qualified GHC.Exts - import Control.Monad.Morph (MFunctor (..)) -@@ -151,11 +154,19 @@ - go (HaveOutput p c o) = HaveOutput (go p) c o - {-# INLINE catch #-} - -+#if MIN_VERSION_base(4,9,0) -+instance Monad m => Semigroup (Pipe l i o u m ()) where -+ (<>) = (>>) -+ {-# INLINE (<>) #-} -+#endif -+ - instance Monad m => Monoid (Pipe l i o u m ()) where - mempty = return () - {-# INLINE mempty #-} -+#if MIN_VERSION_base(4,11,0) - mappend = (>>) - {-# INLINE mappend #-} -+#endif - - instance PrimMonad m => PrimMonad (Pipe l i o u m) where - type PrimState (Pipe l i o u m) = PrimState m diff --git a/patches/constraints-0.10.patch b/patches/constraints-0.10.patch deleted file mode 100644 index d3de932d7d956d3c0ca254462087d00006b5f74b..0000000000000000000000000000000000000000 --- a/patches/constraints-0.10.patch +++ /dev/null @@ -1,13 +0,0 @@ -diff -ru constraints-0.10.orig/src/Data/Constraint/Nat.hs constraints-0.10/src/Data/Constraint/Nat.hs ---- constraints-0.10.orig/src/Data/Constraint/Nat.hs 2018-01-18 14:26:31.000000000 -0500 -+++ constraints-0.10/src/Data/Constraint/Nat.hs 2018-06-24 18:17:26.938269657 -0400 -@@ -10,6 +10,9 @@ - {-# LANGUAGE ScopedTypeVariables #-} - {-# LANGUAGE AllowAmbiguousTypes #-} - {-# LANGUAGE Trustworthy #-} -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - -- | Utilities for working with 'KnownNat' constraints. - -- - -- This module is only available on GHC 8.0 or later. diff --git a/patches/constraints-0.9.1.patch b/patches/constraints-0.9.1.patch deleted file mode 100644 index c3292e7c4d48e5b8bcbc47d7782229fe7a8ca711..0000000000000000000000000000000000000000 --- a/patches/constraints-0.9.1.patch +++ /dev/null @@ -1,147 +0,0 @@ -diff -ru constraints-0.9.1.orig/constraints.cabal constraints-0.9.1/constraints.cabal ---- constraints-0.9.1.orig/constraints.cabal 2017-12-14 16:01:10.333221877 +0000 -+++ constraints-0.9.1/constraints.cabal 2017-12-14 16:01:51.188356699 +0000 -@@ -48,6 +48,7 @@ - ghc-prim, - hashable >= 1.2 && < 1.3, - mtl >= 2 && < 2.3, -+ semigroups >= 0.11 && < 0.19, - transformers >= 0.2 && < 0.6, - transformers-compat >= 0.4 && < 1 - -diff -ru constraints-0.9.1.orig/src/Data/Constraint/Lifting.hs constraints-0.9.1/src/Data/Constraint/Lifting.hs ---- constraints-0.9.1.orig/src/Data/Constraint/Lifting.hs 2017-03-13 14:35:11.000000000 +0000 -+++ constraints-0.9.1/src/Data/Constraint/Lifting.hs 2017-12-14 16:01:51.188356699 +0000 -@@ -54,6 +54,9 @@ - import Data.Monoid - #endif - import Data.Ratio -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup -+#endif - #if __GLASGOW_HASKELL__ < 710 - import Data.Traversable - #endif -@@ -77,6 +80,7 @@ - instance Lifting Hashable Maybe where lifting = Sub Dict - instance Lifting Binary Maybe where lifting = Sub Dict - instance Lifting NFData Maybe where lifting = Sub Dict -+instance Lifting Semigroup Maybe where lifting = Sub Dict - instance Lifting Monoid Maybe where lifting = Sub Dict - - instance Lifting Eq Ratio where lifting = Sub Dict -@@ -85,7 +89,7 @@ - instance Lifting Eq Complex where lifting = Sub Dict - instance Lifting Read Complex where lifting = Sub Dict - instance Lifting Show Complex where lifting = Sub Dict -- -+instance Lifting Semigroup ((->) a) where lifting = Sub Dict - instance Lifting Monoid ((->) a) where lifting = Sub Dict - - instance Eq a => Lifting Eq (Either a) where lifting = Sub Dict -@@ -103,6 +107,7 @@ - instance Hashable a => Lifting Hashable ((,) a) where lifting = Sub Dict - instance Binary a => Lifting Binary ((,) a) where lifting = Sub Dict - instance NFData a => Lifting NFData ((,) a) where lifting = Sub Dict -+instance Semigroup a => Lifting Semigroup ((,) a) where lifting = Sub Dict - instance Monoid a => Lifting Monoid ((,) a) where lifting = Sub Dict - instance Bounded a => Lifting Bounded ((,) a) where lifting = Sub Dict - instance Ix a => Lifting Ix ((,) a) where lifting = Sub Dict -@@ -434,6 +439,7 @@ - instance Lifting2 Hashable (,) where lifting2 = Sub Dict - instance Lifting2 Binary (,) where lifting2 = Sub Dict - instance Lifting2 NFData (,) where lifting2 = Sub Dict -+instance Lifting2 Semigroup (,) where lifting2 = Sub Dict - instance Lifting2 Monoid (,) where lifting2 = Sub Dict - instance Lifting2 Bounded (,) where lifting2 = Sub Dict - instance Lifting2 Ix (,) where lifting2 = Sub Dict -diff -ru constraints-0.9.1.orig/src/Data/Constraint/Nat.hs constraints-0.9.1/src/Data/Constraint/Nat.hs ---- constraints-0.9.1.orig/src/Data/Constraint/Nat.hs 2017-03-13 14:35:11.000000000 +0000 -+++ constraints-0.9.1/src/Data/Constraint/Nat.hs 2017-12-14 16:05:49.260898238 +0000 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DataKinds #-} - {-# LANGUAGE PolyKinds #-} - {-# LANGUAGE RankNTypes #-} -@@ -42,7 +43,11 @@ - - import Data.Constraint - import Data.Proxy -+#if __GLASGOW_HASKELL__ > 802 -+import GHC.TypeLits hiding (type Div, type Mod) -+#else - import GHC.TypeLits -+#endif - import Unsafe.Coerce - - type family Min :: Nat -> Nat -> Nat where -diff -ru constraints-0.9.1.orig/src/Data/Constraint.hs constraints-0.9.1/src/Data/Constraint.hs ---- constraints-0.9.1.orig/src/Data/Constraint.hs 2017-03-13 14:35:11.000000000 +0000 -+++ constraints-0.9.1/src/Data/Constraint.hs 2017-12-14 16:08:52.823606547 +0000 -@@ -76,11 +76,11 @@ - import Control.Applicative - import Control.Category - import Control.Monad --#if __GLASGOW_HASKELL__ < 710 --import Data.Monoid --#endif - import Data.Complex - import Data.Ratio -+#if __GLASGOW_HASKELL__ <= 802 -+import Data.Semigroup -+#endif - import Data.Data - import qualified GHC.Exts as Exts (Any) - import GHC.Exts (Constraint) -@@ -618,8 +618,27 @@ - instance RealFloat a :=> RealFloat (Const a b) where ins = Sub Dict - #endif - -+-- Semigroup -+instance Class () (Semigroup a) where cls = Sub Dict -+instance () :=> Semigroup () where ins = Sub Dict -+instance () :=> Semigroup Ordering where ins = Sub Dict -+instance () :=> Semigroup [a] where ins = Sub Dict -+instance Semigroup a :=> Semigroup (Maybe a) where ins = Sub Dict -+instance (Semigroup a, Semigroup b) :=> Semigroup (a, b) where ins = Sub Dict -+instance Semigroup a :=> Semigroup (Const a b) where ins = Sub Dict -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup a :=> Semigroup (Identity a) where ins = Sub Dict -+#endif -+#if MIN_VERSION_base(4,10,0) -+instance Semigroup a :=> Semigroup (IO a) where ins = Sub Dict -+#endif -+ - -- Monoid -+#if MIN_VERSION_base(4,11,0) -+instance Class (Semigroup a) (Monoid a) where cls = Sub Dict -+#else - instance Class () (Monoid a) where cls = Sub Dict -+#endif - instance () :=> Monoid () where ins = Sub Dict - instance () :=> Monoid Ordering where ins = Sub Dict - instance () :=> Monoid [a] where ins = Sub Dict -@@ -628,8 +647,6 @@ - instance Monoid a :=> Monoid (Const a b) where ins = Sub Dict - #if MIN_VERSION_base(4,9,0) - instance Monoid a :=> Monoid (Identity a) where ins = Sub Dict --#endif --#if MIN_VERSION_base(4,9,0) - instance Monoid a :=> Monoid (IO a) where ins = Sub Dict - #endif - -@@ -700,7 +717,13 @@ - instance a :=> Read (Dict a) where ins = Sub Dict - deriving instance a => Read (Dict a) - -+instance () :=> Semigroup (Dict a) where ins = Sub Dict -+instance Semigroup (Dict a) where -+ Dict <> Dict = Dict -+ - instance a :=> Monoid (Dict a) where ins = Sub Dict - instance a => Monoid (Dict a) where -- mappend Dict Dict = Dict -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - mempty = Dict diff --git a/patches/contravariant-1.4.1.patch b/patches/contravariant-1.4.1.patch deleted file mode 100644 index c8176e47ed57f908dee10e8bd04d79ae6acf8ba1..0000000000000000000000000000000000000000 --- a/patches/contravariant-1.4.1.patch +++ /dev/null @@ -1,117 +0,0 @@ -From 2ba79e6a8b249783eddbebe124e5cd0382a4107b Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Fri, 20 Apr 2018 10:20:29 -0400 -Subject: [PATCH] Support building with GHC 8.5 (#45) - -* Support building with GHC 8.5 - -* Require a Contravariant-supporting StateVar ---- - CHANGELOG.markdown | 5 +++++ - contravariant.cabal | 7 +++++-- - {src => old-src}/Data/Functor/Contravariant.hs | 12 ++++++------ - 4 files changed, 36 insertions(+), 9 deletions(-) - rename {src => old-src}/Data/Functor/Contravariant.hs (98%) - -diff --git a/CHANGELOG.markdown b/CHANGELOG.markdown -index a12e8bf..a8b83a9 100644 ---- a/CHANGELOG.markdown -+++ b/CHANGELOG.markdown -@@ -1,3 +1,8 @@ -+next [????.??.??] -+----------------- -+* Support building with GHC 8.6, where `Data.Functor.Contravariant` has been -+ moved into `base`. -+ - 1.4.1 [2018.01.18] - ------------------ - * Add `Semigroup` and `Monoid` instances for `Predicate`. -diff --git a/contravariant.cabal b/contravariant.cabal -index 70df61e..f4459c9 100644 ---- a/contravariant.cabal -+++ b/contravariant.cabal -@@ -78,7 +78,7 @@ library - build-depends: semigroups >= 0.15.2 && < 1 - - if flag(StateVar) -- build-depends: StateVar >= 1.1 && < 1.2 -+ build-depends: StateVar >= 1.1.1 && < 1.2 - - if impl(ghc >= 7.2 && < 7.6) - build-depends: ghc-prim -@@ -87,10 +87,13 @@ library - cpp-options: -DSAFE - - exposed-modules: -- Data.Functor.Contravariant - Data.Functor.Contravariant.Compose - Data.Functor.Contravariant.Divisible - -+ if impl(ghc < 8.5) -+ hs-source-dirs: old-src -+ exposed-modules: Data.Functor.Contravariant -+ - if impl(ghc >= 7.4) - exposed-modules: Data.Functor.Contravariant.Generic - -diff --git a/src/Data/Functor/Contravariant.hs b/old-src/Data/Functor/Contravariant.hs -similarity index 98% -rename from src/Data/Functor/Contravariant.hs -rename to old-src/Data/Functor/Contravariant.hs -index 8096afd..a2be28d 100644 ---- a/src/Data/Functor/Contravariant.hs -+++ b/old-src/Data/Functor/Contravariant.hs -@@ -181,7 +181,7 @@ infixl 4 >$, $<, >$<, >$$< - ($<) = flip (>$) - {-# INLINE ($<) #-} - ---- | This is an infix alias for 'contramap' -+-- | This is an infix alias for 'contramap'. - (>$<) :: Contravariant f => (a -> b) -> f b -> f a - (>$<) = contramap - {-# INLINE (>$<) #-} -@@ -201,7 +201,7 @@ instance Contravariant V1 where - contramap _ x = x `seq` undefined - - instance Contravariant U1 where -- contramap _ U1 = U1 -+ contramap _ _ = U1 - - instance Contravariant f => Contravariant (Rec1 f) where - contramap f (Rec1 fp)= Rec1 (contramap f fp) -@@ -297,7 +297,7 @@ instance Contravariant SettableStateVar where - - #if (__GLASGOW_HASKELL__ >= 707) || defined(VERSION_tagged) - instance Contravariant Proxy where -- contramap _ Proxy = Proxy -+ contramap _ _ = Proxy - #endif - - newtype Predicate a = Predicate { getPredicate :: a -> Bool } -@@ -323,7 +323,7 @@ instance Monoid (Predicate a) where - mappend (Predicate p) (Predicate q) = Predicate $ \a -> p a && q a - #endif - ---- | Defines a total ordering on a type as per 'compare' -+-- | Defines a total ordering on a type as per 'compare'. - -- - -- This condition is not checked by the types. You must ensure that the supplied - -- values are valid total orderings yourself. -@@ -346,7 +346,7 @@ instance Monoid (Comparison a) where - mempty = Comparison (\_ _ -> EQ) - mappend (Comparison p) (Comparison q) = Comparison $ mappend p q - ---- | Compare using 'compare' -+-- | Compare using 'compare'. - defaultComparison :: Ord a => Comparison a - defaultComparison = Comparison compare - -@@ -391,7 +391,7 @@ instance Monoid (Equivalence a) where - mempty = Equivalence (\_ _ -> True) - mappend (Equivalence p) (Equivalence q) = Equivalence $ \a b -> p a b && q a b - ---- | Check for equivalence with '==' -+-- | Check for equivalence with '=='. - -- - -- Note: The instances for 'Double' and 'Float' violate reflexivity for @NaN@. - defaultEquivalence :: Eq a => Equivalence a diff --git a/patches/criterion-1.2.2.0.patch b/patches/criterion-1.2.2.0.patch deleted file mode 100644 index 0d751f7c90826b13a80006ff4e2a77c2ceb12c94..0000000000000000000000000000000000000000 --- a/patches/criterion-1.2.2.0.patch +++ /dev/null @@ -1,43 +0,0 @@ -diff -ru criterion-1.2.2.0.orig/Criterion/Types.hs criterion-1.2.2.0/Criterion/Types.hs ---- criterion-1.2.2.0.orig/Criterion/Types.hs 2017-08-05 18:35:19.000000000 +0200 -+++ criterion-1.2.2.0/Criterion/Types.hs 2017-09-15 11:45:03.538012575 +0200 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE Trustworthy #-} - {-# LANGUAGE RankNTypes #-} - {-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GADTs, RecordWildCards #-} -@@ -74,6 +75,7 @@ - -- Temporary: to support pre-AMP GHC 7.8.4: - import Control.Applicative - import Data.Monoid -+import Data.Semigroup - - import Control.DeepSeq (NFData(rnf)) - import Control.Exception (evaluate) -@@ -650,9 +652,14 @@ - _ -> fail $ "get for OutlierEffect: unexpected " ++ show i - instance NFData OutlierEffect - -+instance Semigroup Outliers where -+ (<>) = addOutliers -+ - instance Monoid Outliers where - mempty = Outliers 0 0 0 0 0 -+#if !(MIN_VERSION_base(4,11,0)) - mappend = addOutliers -+#endif - - addOutliers :: Outliers -> Outliers -> Outliers - addOutliers (Outliers s a b c d) (Outliers t w x y z) = -Only in criterion-1.2.2.0/Criterion: Types.hs.orig -diff -ru criterion-1.2.2.0.orig/criterion.cabal criterion-1.2.2.0/criterion.cabal ---- criterion-1.2.2.0.orig/criterion.cabal 2017-08-05 18:35:19.000000000 +0200 -+++ criterion-1.2.2.0/criterion.cabal 2017-09-15 11:45:03.542012553 +0200 -@@ -101,6 +101,7 @@ - mwc-random >= 0.8.0.3, - optparse-applicative >= 0.13, - parsec >= 3.1.0, -+ semigroups, - statistics >= 0.14 && < 0.15, - text >= 0.11, - time, diff --git a/patches/criterion-1.2.6.0.patch b/patches/criterion-1.2.6.0.patch deleted file mode 100644 index eaf30675db82b6e70e7b623ad1540074bdffe799..0000000000000000000000000000000000000000 --- a/patches/criterion-1.2.6.0.patch +++ /dev/null @@ -1,110 +0,0 @@ -commit dd847e8d29133f5a5c420e728023f92e2023c283 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Dec 28 11:21:03 2017 -0500 - - Remove deprecated GCStats-based interface - - Fixes #171. - -diff --git a/Criterion/Measurement.hs b/Criterion/Measurement.hs -index d352bf6..d006933 100644 ---- a/Criterion/Measurement.hs -+++ b/Criterion/Measurement.hs -@@ -5,12 +5,6 @@ - {-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface, - ScopedTypeVariables #-} - --#if MIN_VERSION_base(4,10,0) ---- Disable deprecation warnings for now until we remove the use of getGCStats ---- and applyGCStats for good --{-# OPTIONS_GHC -Wno-deprecations #-} --#endif -- - -- | - -- Module : Criterion.Measurement - -- Copyright : (c) 2009-2014 Bryan O'Sullivan -@@ -38,9 +32,6 @@ module Criterion.Measurement - , measured - , applyGCStatistics - , threshold -- -- * Deprecated -- , getGCStats -- , applyGCStats - ) where - - import Criterion.Types (Benchmarkable(..), Measured(..)) -@@ -52,9 +43,10 @@ import Data.Int (Int64) - import Data.List (unfoldr) - import Data.Word (Word64) - import GHC.Generics (Generic) --import GHC.Stats (GCStats(..)) - #if MIN_VERSION_base(4,10,0) - import GHC.Stats (RTSStats(..), GCDetails(..)) -+#else -+import GHC.Stats (GCStats(..)) - #endif - import System.Mem (performGC) - import Text.Printf (printf) -@@ -66,9 +58,9 @@ import qualified GHC.Stats as Stats - -- 'gcStatsCurrentBytesUsed' and 'gcStatsCurrentBytesSlop' all are cumulative values since - -- the program started. - -- ---- 'GCStatistics' is cargo-culted from the 'GCStats' data type that "GHC.Stats" ---- has. Since 'GCStats' was marked as deprecated and will be removed in GHC 8.4, ---- we use 'GCStatistics' to provide a backwards-compatible view of GC statistics. -+-- 'GCStatistics' is cargo-culted from the @GCStats@ data type that "GHC.Stats" -+-- used to export. Since @GCStats@ was removed in GHC 8.4, @criterion@ uses -+-- 'GCStatistics' to provide a backwards-compatible view of GC statistics. - data GCStatistics = GCStatistics - { -- | Total number of bytes allocated - gcStatsBytesAllocated :: !Int64 -@@ -115,18 +107,6 @@ data GCStatistics = GCStatistics - -- | Try to get GC statistics, bearing in mind that the GHC runtime - -- will throw an exception if statistics collection was not enabled - -- using \"@+RTS -T@\". --{-# DEPRECATED getGCStats -- ["GCStats has been deprecated in GHC 8.2. As a consequence,", -- "getGCStats has also been deprecated in favor of getGCStatistics.", -- "getGCStats will be removed in the next major criterion release."] #-} --getGCStats :: IO (Maybe GCStats) --getGCStats = -- (Just `fmap` Stats.getGCStats) `Exc.catch` \(_::Exc.SomeException) -> -- return Nothing -- ---- | Try to get GC statistics, bearing in mind that the GHC runtime ---- will throw an exception if statistics collection was not enabled ---- using \"@+RTS -T@\". - getGCStatistics :: IO (Maybe GCStatistics) - #if MIN_VERSION_base(4,10,0) - -- Use RTSStats/GCDetails to gather GC stats -@@ -331,30 +311,6 @@ measured = Measured { - - -- | Apply the difference between two sets of GC statistics to a - -- measurement. --{-# DEPRECATED applyGCStats -- ["GCStats has been deprecated in GHC 8.2. As a consequence,", -- "applyGCStats has also been deprecated in favor of applyGCStatistics.", -- "applyGCStats will be removed in the next major criterion release."] #-} --applyGCStats :: Maybe GCStats -- -- ^ Statistics gathered at the __end__ of a run. -- -> Maybe GCStats -- -- ^ Statistics gathered at the __beginning__ of a run. -- -> Measured -- -- ^ Value to \"modify\". -- -> Measured --applyGCStats (Just end) (Just start) m = m { -- measAllocated = diff bytesAllocated -- , measNumGcs = diff numGcs -- , measBytesCopied = diff bytesCopied -- , measMutatorWallSeconds = diff mutatorWallSeconds -- , measMutatorCpuSeconds = diff mutatorCpuSeconds -- , measGcWallSeconds = diff gcWallSeconds -- , measGcCpuSeconds = diff gcCpuSeconds -- } where diff f = f end - f start --applyGCStats _ _ m = m -- ---- | Apply the difference between two sets of GC statistics to a ---- measurement. - applyGCStatistics :: Maybe GCStatistics - -- ^ Statistics gathered at the __end__ of a run. - -> Maybe GCStatistics diff --git a/patches/css-text-0.1.2.2.patch b/patches/css-text-0.1.2.2.patch deleted file mode 100644 index d48e6754230d70ceefdc9cbae5ffed53cac6028c..0000000000000000000000000000000000000000 --- a/patches/css-text-0.1.2.2.patch +++ /dev/null @@ -1,67 +0,0 @@ -From 176c321ccc49b229ec89fc2e790d8abd74ca3d67 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue, 23 Jan 2018 20:23:18 -0500 -Subject: [PATCH 1/2] Fix the build on GHC 8.4 - ---- - Text/CSS/Render.hs | 6 ++---- - css-text.cabal | 4 ++++ - 2 files changed, 6 insertions(+), 4 deletions(-) - -diff --git a/Text/CSS/Render.hs b/Text/CSS/Render.hs -index b68773f..d3aa106 100644 ---- a/Text/CSS/Render.hs -+++ b/Text/CSS/Render.hs -@@ -10,12 +10,10 @@ module Text.CSS.Render - - import Data.Text (Text) - import Data.Text.Lazy.Builder (Builder, fromText, singleton) --import Data.Monoid (mappend, mempty, mconcat) -+import Data.Monoid (mempty, mconcat) -+import Data.Semigroup ((<>)) - import Text.CSS.Parse - --(<>) :: Builder -> Builder -> Builder --(<>) = mappend -- - renderAttr :: (Text, Text) -> Builder - renderAttr (k, v) = fromText k <> singleton ':' <> fromText v - -diff --git a/css-text.cabal b/css-text.cabal -index cd10659..4fa558f 100644 ---- a/css-text.cabal -+++ b/css-text.cabal -@@ -16,6 +16,10 @@ library - build-depends: base >= 4 && < 5 - , text >= 0.11 - , attoparsec >= 0.10.2.0 -+ -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups >= 0.16.1 -+ - exposed-modules: Text.CSS.Parse - Text.CSS.Render - ghc-options: -Wall - -From e1b1eaa811ff59329b1cac861c655eb1b8fba869 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Wed, 24 Jan 2018 11:00:07 -0500 -Subject: [PATCH 2/2] Fix indentation - ---- - css-text.cabal | 2 +- - 1 file changed, 1 insertion(+), 1 deletion(-) - -diff --git a/css-text.cabal b/css-text.cabal -index 4fa558f..a568a57 100644 ---- a/css-text.cabal -+++ b/css-text.cabal -@@ -18,7 +18,7 @@ library - , attoparsec >= 0.10.2.0 - - if !impl(ghc >= 8.0) -- build-depends: semigroups >= 0.16.1 -+ build-depends: semigroups >= 0.16.1 - - exposed-modules: Text.CSS.Parse - Text.CSS.Render diff --git a/patches/cubicbezier-0.6.0.4.patch b/patches/cubicbezier-0.6.0.4.patch deleted file mode 100644 index c82c7be2c3d73930dfe8d6ff3b010d82bdd610b8..0000000000000000000000000000000000000000 --- a/patches/cubicbezier-0.6.0.4.patch +++ /dev/null @@ -1,75 +0,0 @@ -From 6aa4e9511a7aa3e03e0464790e419e1b266974b3 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu, 25 Jan 2018 12:42:46 -0500 -Subject: [PATCH 1/2] Add a Semigroup instance for OpenPath - ---- - Geom2D/CubicBezier/Basic.hs | 18 +++++++++++++----- - 1 file changed, 13 insertions(+), 5 deletions(-) - -diff --git a/Geom2D/CubicBezier/Basic.hs b/Geom2D/CubicBezier/Basic.hs -index 92de359..87b63d6 100644 ---- a/Geom2D/CubicBezier/Basic.hs -+++ b/Geom2D/CubicBezier/Basic.hs -@@ -1,5 +1,5 @@ - {-# LANGUAGE PatternGuards #-} --{-# LANGUAGE BangPatterns, FlexibleInstances, MultiParamTypeClasses, DeriveTraversable, ViewPatterns, PatternSynonyms, MultiWayIf #-} -+{-# LANGUAGE BangPatterns, CPP, FlexibleInstances, MultiParamTypeClasses, DeriveTraversable, ViewPatterns, PatternSynonyms, MultiWayIf #-} - module Geom2D.CubicBezier.Basic - (CubicBezier (..), QuadBezier (..), AnyBezier (..), GenericBezier(..), - PathJoin (..), ClosedPath(..), OpenPath (..), AffineTransform (..), anyToCubic, anyToQuad, -@@ -16,6 +16,9 @@ import Geom2D.CubicBezier.Numeric - import Math.BernsteinPoly - import Numeric.Integration.TanhSinh - import Data.Monoid () -+#if !MIN_VERSION_base(4,11,0) -+import Data.Semigroup (Semigroup(..)) -+#endif - import Data.List (minimumBy) - import Data.Function (on) - import Data.VectorSpace -@@ -93,12 +96,17 @@ data OpenPath a = OpenPath [(Point a, PathJoin a)] (Point a) - data ClosedPath a = ClosedPath [(Point a, PathJoin a)] - deriving (Show, Functor, Foldable, Traversable) - -+instance Semigroup (OpenPath a) where -+ p1 <> OpenPath [] _ = p1 -+ OpenPath [] _ <> p2 = p2 -+ OpenPath joins1 _ <> OpenPath joins2 p = -+ OpenPath (joins1 ++ joins2) p -+ - instance Monoid (OpenPath a) where - mempty = OpenPath [] (error "empty path") -- mappend p1 (OpenPath [] _) = p1 -- mappend (OpenPath [] _) p2 = p2 -- mappend (OpenPath joins1 _) (OpenPath joins2 p) = -- OpenPath (joins1 ++ joins2) p -+#if !MIN_VERSION_base(4,11,0) -+ mappend = (<>) -+#endif - - instance (Num a) => AffineTransform (PathJoin a) a where - transform _ JoinLine = JoinLine - -From 6660bc91cb7511a58cb44cf81f91e037d2777381 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu, 25 Jan 2018 12:47:04 -0500 -Subject: [PATCH 2/2] Depend on semigroups for compatibility - ---- - cubicbezier.cabal | 2 ++ - 1 file changed, 2 insertions(+) - -diff --git a/cubicbezier.cabal b/cubicbezier.cabal -index 8f8642b..a2cecf8 100644 ---- a/cubicbezier.cabal -+++ b/cubicbezier.cabal -@@ -36,6 +36,8 @@ Library - Build-depends: base >= 4.8 && < 5, containers >= 0.5.3, integration >= 0.1.1, vector >= 0.10, - matrices >= 0.4.1, microlens >= 0.1.2, microlens-th >= 0.1.2, microlens-mtl >= 0.1.2, mtl >= 2.1.1, - fast-math >= 1.0.0, vector-space >= 0.10.4 -+ if !impl(ghc>=8.0) -+ Build-depends: semigroups >= 0.16 - Exposed-Modules: - Geom2D - Geom2D.CubicBezier diff --git a/patches/diagrams-cairo-1.4.patch b/patches/diagrams-cairo-1.4.patch deleted file mode 100644 index 121a9e4bb4947f14842edfed51e4b7f2b12a220f..0000000000000000000000000000000000000000 --- a/patches/diagrams-cairo-1.4.patch +++ /dev/null @@ -1,31 +0,0 @@ -commit 2e13ce61eaca7728a520263d09ab2b697d888557 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Mon Feb 26 12:34:35 2018 -0500 - - Add a Semigroup (Render Cairo V2 Double) instance - -diff --git a/src/Diagrams/Backend/Cairo/Internal.hs b/src/Diagrams/Backend/Cairo/Internal.hs -index 07facfb..5fba6ad 100644 ---- a/src/Diagrams/Backend/Cairo/Internal.hs -+++ b/src/Diagrams/Backend/Cairo/Internal.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DeriveDataTypeable #-} - {-# LANGUAGE DeriveGeneric #-} - {-# LANGUAGE ExistentialQuantification #-} -@@ -178,9 +179,14 @@ instance Backend Cairo V2 Double where - runC :: Render Cairo V2 Double -> RenderM () - runC (C r) = r - -+instance Semigroup (Render Cairo V2 Double) where -+ C rd1 <> C rd2 = C (rd1 >> rd2) -+ - instance Monoid (Render Cairo V2 Double) where - mempty = C $ return () -- (C rd1) `mappend` (C rd2) = C (rd1 >> rd2) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - instance Hashable (Options Cairo V2 Double) where - hashWithSalt s (CairoOptions fn sz out adj) diff --git a/patches/diagrams-canvas-1.4.patch b/patches/diagrams-canvas-1.4.patch deleted file mode 100644 index f418b505b0be7ce9d4632b218fad91468bbc9af1..0000000000000000000000000000000000000000 --- a/patches/diagrams-canvas-1.4.patch +++ /dev/null @@ -1,31 +0,0 @@ -commit fff85f0069f2539c1f51427803ec8ca1cd7b8bd7 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 11:20:41 2018 -0500 - - Add a Semigroup (Render Canvas V2 Double) instance - -diff --git a/src/Diagrams/Backend/Canvas.hs b/src/Diagrams/Backend/Canvas.hs -index 154cf45..67f5309 100644 ---- a/src/Diagrams/Backend/Canvas.hs -+++ b/src/Diagrams/Backend/Canvas.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE TypeFamilies #-} - {-# LANGUAGE MultiParamTypeClasses #-} - {-# LANGUAGE FlexibleInstances #-} -@@ -136,9 +137,14 @@ liftC = lift - runRenderM :: RenderM a -> BC.Canvas a - runRenderM = flip SS.evalStateStackT def - -+instance Semigroup (Render Canvas V2 Double) where -+ C c1 <> C c2 = C (c1 >> c2) -+ - instance Monoid (Render Canvas V2 Double) where - mempty = C $ return () -- (C c1) `mappend` (C c2) = C (c1 >> c2) -+#if !MIN_VERSION_base(4,11,0) -+ mappend = (<>) -+#endif - - instance Backend Canvas V2 Double where - data Render Canvas V2 Double = C (RenderM ()) diff --git a/patches/diagrams-contrib-1.4.1.patch b/patches/diagrams-contrib-1.4.1.patch deleted file mode 100644 index 4d48854a1f94e164c0b5c3f737f4c4727a2297b0..0000000000000000000000000000000000000000 --- a/patches/diagrams-contrib-1.4.1.patch +++ /dev/null @@ -1,19 +0,0 @@ -commit ee6a976add3f2596824a272e3b01d02cd7898537 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 12:59:48 2018 -0500 - - Add a Semigroup instance for Following - -diff --git a/src/Diagrams/TwoD/Path/Follow.hs b/src/Diagrams/TwoD/Path/Follow.hs -index 585913b..412acdf 100644 ---- a/src/Diagrams/TwoD/Path/Follow.hs -+++ b/src/Diagrams/TwoD/Path/Follow.hs -@@ -61,7 +61,7 @@ import Data.Monoid.SemiDirectProduct.Strict - -- - newtype Following n - = Following { unFollowing :: Semi (Trail' Line V2 n) (Angle n) } -- deriving (Monoid) -+ deriving (Monoid, Semigroup) - - -- | Note this is only an iso when considering trails equivalent up to - -- rotation. diff --git a/patches/diagrams-contrib-1.4.2.1.patch b/patches/diagrams-contrib-1.4.2.1.patch deleted file mode 100644 index 897db30706f83ddc8accb1907ec71b5a63fb5407..0000000000000000000000000000000000000000 --- a/patches/diagrams-contrib-1.4.2.1.patch +++ /dev/null @@ -1,19 +0,0 @@ -commit 01c6185d317d4171c08908074ab01d83fc694ceb -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Mon Feb 26 12:40:06 2018 -0500 - - Add a Semigroup instance for Following - -diff --git a/src/Diagrams/TwoD/Path/Follow.hs b/src/Diagrams/TwoD/Path/Follow.hs -index 585913b..412acdf 100644 ---- a/src/Diagrams/TwoD/Path/Follow.hs -+++ b/src/Diagrams/TwoD/Path/Follow.hs -@@ -61,7 +61,7 @@ import Data.Monoid.SemiDirectProduct.Strict - -- - newtype Following n - = Following { unFollowing :: Semi (Trail' Line V2 n) (Angle n) } -- deriving (Monoid) -+ deriving (Monoid, Semigroup) - - -- | Note this is only an iso when considering trails equivalent up to - -- rotation. diff --git a/patches/diagrams-core-1.4.0.1.patch b/patches/diagrams-core-1.4.0.1.patch deleted file mode 100644 index 759bd9f3097f6cf6c62fa24af408d03577cf11dc..0000000000000000000000000000000000000000 --- a/patches/diagrams-core-1.4.0.1.patch +++ /dev/null @@ -1,27 +0,0 @@ -commit 2f7655be01d0f983de3ad91f2a0ad936fa5c875d -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 10:54:41 2018 -0500 - - Add a Semigroup (Render NullBackend v n) instance - -diff --git a/src/Diagrams/Core/Types.hs b/src/Diagrams/Core/Types.hs -index 56b86ab..625eea2 100644 ---- a/src/Diagrams/Core/Types.hs -+++ b/src/Diagrams/Core/Types.hs -@@ -966,9 +966,14 @@ data NullBackend - -- - -- because it overlaps with the Renderable instance for NullPrim. - -+instance Semigroup (Render NullBackend v n) where -+ _ <> _ = NullBackendRender -+ - instance Monoid (Render NullBackend v n) where -- mempty = NullBackendRender -- mappend _ _ = NullBackendRender -+ mempty = NullBackendRender -+#if !MIN_VERSION_base(4,11,0) -+ mappend = (<>) -+#endif - - instance Backend NullBackend v n where - data Render NullBackend v n = NullBackendRender diff --git a/patches/diagrams-lib-1.4.2.patch b/patches/diagrams-lib-1.4.2.patch deleted file mode 100644 index 55e5056beef49380afd66e835626ac16e21c2d29..0000000000000000000000000000000000000000 --- a/patches/diagrams-lib-1.4.2.patch +++ /dev/null @@ -1,19 +0,0 @@ -commit e3e6be2e963a4ee26c432ce3472b9f27c711a985 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 11:05:12 2018 -0500 - - Add a Semigroup instnce for SegTree - -diff --git a/src/Diagrams/Trail.hs b/src/Diagrams/Trail.hs -index e5123cd..1401866 100644 ---- a/src/Diagrams/Trail.hs -+++ b/src/Diagrams/Trail.hs -@@ -174,7 +174,7 @@ instance (FT.Measured m a, FT.Measured n b) - -- beginning which have a combined arc length of at least 5). - - newtype SegTree v n = SegTree (FingerTree (SegMeasure v n) (Segment Closed v n)) -- deriving (Eq, Ord, Show, Monoid, Transformable, FT.Measured (SegMeasure v n)) -+ deriving (Eq, Ord, Show, Monoid, Semigroup, Transformable, FT.Measured (SegMeasure v n)) - - instance Wrapped (SegTree v n) where - type Unwrapped (SegTree v n) = FingerTree (SegMeasure v n) (Segment Closed v n) diff --git a/patches/diagrams-postscript-1.4.patch b/patches/diagrams-postscript-1.4.patch deleted file mode 100644 index d21e151325ba3a6fb6767d91329589b9429e4214..0000000000000000000000000000000000000000 --- a/patches/diagrams-postscript-1.4.patch +++ /dev/null @@ -1,32 +0,0 @@ -commit 44852bb73ee4f34a1fc304bac562dbf0027c9806 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 11:36:46 2018 -0500 - - Add Semigroup (Render Postscript V2 Double) instance - -diff --git a/src/Diagrams/Backend/Postscript.hs b/src/Diagrams/Backend/Postscript.hs -index 76ef03e..19fcfc6 100644 ---- a/src/Diagrams/Backend/Postscript.hs -+++ b/src/Diagrams/Backend/Postscript.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DeriveDataTypeable #-} - {-# LANGUAGE DeriveGeneric #-} - {-# LANGUAGE FlexibleContexts #-} -@@ -123,10 +124,14 @@ save = SS.save >> liftC C.save - restore :: RenderM () - restore = liftC C.restore >> SS.restore - -+instance Semigroup (Render Postscript V2 Double) where -+ C x <> C y = C (x >> y) -+ - instance Monoid (Render Postscript V2 Double) where - mempty = C $ return () -- (C x) `mappend` (C y) = C (x >> y) -- -+#if !MIN_VERSION_base(4,11,0) -+ mappend = (<>) -+#endif - - instance Backend Postscript V2 Double where - data Render Postscript V2 Double = C (RenderM ()) diff --git a/patches/diagrams-svg-1.4.1.1.patch b/patches/diagrams-svg-1.4.1.1.patch deleted file mode 100644 index 8dff38f56bd7c1ba801d4c4da3275a384033f106..0000000000000000000000000000000000000000 --- a/patches/diagrams-svg-1.4.1.1.patch +++ /dev/null @@ -1,32 +0,0 @@ -commit 9836338542ca40016fb5d401114af09d6a3970c0 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 12:19:36 2018 -0500 - - Add a Semigroup (Render SVG V2 n) instance - -diff --git a/src/Diagrams/Backend/SVG.hs b/src/Diagrams/Backend/SVG.hs -index 75b1b26..96d292c 100644 ---- a/src/Diagrams/Backend/SVG.hs -+++ b/src/Diagrams/Backend/SVG.hs -@@ -194,13 +194,18 @@ runRenderM :: SVGFloat n => T.Text -> SvgRenderM n -> Element - runRenderM o s = flip evalState initialSvgRenderState - $ runReaderT s (initialEnvironment o) - --instance Monoid (Render SVG V2 n) where -- mempty = R $ return mempty -- R r1 `mappend` R r2_ = R $ do -+instance Semigroup (Render SVG V2 n) where -+ R r1 <> R r2_ = R $ do - svg1 <- r1 - svg2 <- r2_ - return (svg1 `mappend` svg2) - -+instance Monoid (Render SVG V2 n) where -+ mempty = R $ return mempty -+#if !MIN_VERSION_base(4,11,0) -+ mappend = (<>) -+#endif -+ - -- Handle clip attributes. - -- - renderSvgWithClipping :: forall n. SVGFloat n diff --git a/patches/doctemplates-0.1.0.2.patch b/patches/doctemplates-0.1.0.2.patch deleted file mode 100644 index 0a7b1767fc2f5d52bf01334b1bac4b7e2643d66f..0000000000000000000000000000000000000000 --- a/patches/doctemplates-0.1.0.2.patch +++ /dev/null @@ -1,21 +0,0 @@ -diff -ru doctemplates-0.1.0.2.orig/src/Text/DocTemplates.hs doctemplates-0.1.0.2/src/Text/DocTemplates.hs ---- doctemplates-0.1.0.2.orig/src/Text/DocTemplates.hs 2016-10-02 11:35:52.000000000 +0200 -+++ doctemplates-0.1.0.2/src/Text/DocTemplates.hs 2017-09-18 12:16:29.323467451 +0200 -@@ -84,6 +84,7 @@ - import Text.Parsec.Text (Parser) - import qualified Data.Set as Set - import Data.Monoid -+import Data.Semigroup (Semigroup(..)) - import Control.Applicative - import qualified Data.Text as T - import Data.Text (Text) -@@ -101,7 +102,7 @@ - -- | A 'Template' is essentially a function that takes - -- a JSON 'Value' and produces 'Text'. - newtype Template = Template { unTemplate :: Value -> Text } -- deriving Monoid -+ deriving (Semigroup,Monoid) - - type Variable = [Text] - -Only in doctemplates-0.1.0.2/src/Text: DocTemplates.hs~ diff --git a/patches/ekg-core-0.1.1.3.patch b/patches/ekg-core-0.1.1.3.patch deleted file mode 100644 index 12be65b35e1c7a1dc6ddbb3fad909f88ddbe6f7d..0000000000000000000000000000000000000000 --- a/patches/ekg-core-0.1.1.3.patch +++ /dev/null @@ -1,200 +0,0 @@ -commit a5cd48ca1c89d387a14482134fb3e4c3bd45bcaf -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Mon Feb 26 18:55:19 2018 -0500 - - Update to the new GHC.Stats API - -diff --git a/System/Metrics.hs b/System/Metrics.hs -index 4daf71d..8b41cff 100644 ---- a/System/Metrics.hs -+++ b/System/Metrics.hs -@@ -331,9 +331,15 @@ createDistribution name store = do - -- easily be added to a metrics store by calling their register - -- function. - -+#if MIN_VERSION_base(4,10,0) -+-- | Convert nanoseconds to milliseconds. -+nsToMs :: Int64 -> Int64 -+nsToMs s = round (realToFrac s / (1000000.0 :: Double)) -+#else - -- | Convert seconds to milliseconds. --toMs :: Double -> Int64 --toMs s = round (s * 1000.0) -+sToMs :: Double -> Int64 -+sToMs s = round (s * 1000.0) -+#endif - - -- | Register a number of metrics related to garbage collector - -- behavior. -@@ -410,18 +416,42 @@ toMs s = round (s * 1000.0) - registerGcMetrics :: Store -> IO () - registerGcMetrics store = - registerGroup -+#if MIN_VERSION_base(4,10,0) -+ (M.fromList -+ [ ("rts.gc.bytes_allocated" , Counter . fromIntegral . Stats.allocated_bytes) -+ , ("rts.gc.num_gcs" , Counter . fromIntegral . Stats.gcs) -+ , ("rts.gc.num_bytes_usage_samples" , Counter . fromIntegral . Stats.major_gcs) -+ , ("rts.gc.cumulative_bytes_used" , Counter . fromIntegral . Stats.cumulative_live_bytes) -+ , ("rts.gc.bytes_copied" , Counter . fromIntegral . Stats.copied_bytes) -+ , ("rts.gc.mutator_cpu_ms" , Counter . nsToMs . Stats.mutator_cpu_ns) -+ , ("rts.gc.mutator_wall_ms" , Counter . nsToMs . Stats.mutator_elapsed_ns) -+ , ("rts.gc.gc_cpu_ms" , Counter . nsToMs . Stats.gc_cpu_ns) -+ , ("rts.gc.gc_wall_ms" , Counter . nsToMs . Stats.gc_elapsed_ns) -+ , ("rts.gc.cpu_ms" , Counter . nsToMs . Stats.cpu_ns) -+ , ("rts.gc.wall_ms" , Counter . nsToMs . Stats.elapsed_ns) -+ , ("rts.gc.max_bytes_used" , Gauge . fromIntegral . Stats.max_live_bytes) -+ , ("rts.gc.current_bytes_used" , Gauge . fromIntegral . Stats.gcdetails_live_bytes . Stats.gc) -+ , ("rts.gc.current_bytes_slop" , Gauge . fromIntegral . Stats.gcdetails_slop_bytes . Stats.gc) -+ , ("rts.gc.max_bytes_slop" , Gauge . fromIntegral . Stats.max_slop_bytes) -+ , ("rts.gc.peak_megabytes_allocated" , Gauge . fromIntegral . (`quot` (1024*1024)) . Stats.max_mem_in_use_bytes) -+ , ("rts.gc.par_tot_bytes_copied" , Gauge . fromIntegral . Stats.par_copied_bytes) -+ , ("rts.gc.par_avg_bytes_copied" , Gauge . fromIntegral . Stats.par_copied_bytes) -+ , ("rts.gc.par_max_bytes_copied" , Gauge . fromIntegral . Stats.cumulative_par_max_copied_bytes) -+ ]) -+ getRTSStats -+#else - (M.fromList - [ ("rts.gc.bytes_allocated" , Counter . Stats.bytesAllocated) - , ("rts.gc.num_gcs" , Counter . Stats.numGcs) - , ("rts.gc.num_bytes_usage_samples" , Counter . Stats.numByteUsageSamples) - , ("rts.gc.cumulative_bytes_used" , Counter . Stats.cumulativeBytesUsed) - , ("rts.gc.bytes_copied" , Counter . Stats.bytesCopied) -- , ("rts.gc.mutator_cpu_ms" , Counter . toMs . Stats.mutatorCpuSeconds) -- , ("rts.gc.mutator_wall_ms" , Counter . toMs . Stats.mutatorWallSeconds) -- , ("rts.gc.gc_cpu_ms" , Counter . toMs . Stats.gcCpuSeconds) -- , ("rts.gc.gc_wall_ms" , Counter . toMs . Stats.gcWallSeconds) -- , ("rts.gc.cpu_ms" , Counter . toMs . Stats.cpuSeconds) -- , ("rts.gc.wall_ms" , Counter . toMs . Stats.wallSeconds) -+ , ("rts.gc.mutator_cpu_ms" , Counter . sToMs . Stats.mutatorCpuSeconds) -+ , ("rts.gc.mutator_wall_ms" , Counter . sToMs . Stats.mutatorWallSeconds) -+ , ("rts.gc.gc_cpu_ms" , Counter . sToMs . Stats.gcCpuSeconds) -+ , ("rts.gc.gc_wall_ms" , Counter . sToMs . Stats.gcWallSeconds) -+ , ("rts.gc.cpu_ms" , Counter . sToMs . Stats.cpuSeconds) -+ , ("rts.gc.wall_ms" , Counter . sToMs . Stats.wallSeconds) - , ("rts.gc.max_bytes_used" , Gauge . Stats.maxBytesUsed) - , ("rts.gc.current_bytes_used" , Gauge . Stats.currentBytesUsed) - , ("rts.gc.current_bytes_slop" , Gauge . Stats.currentBytesSlop) -@@ -432,11 +462,68 @@ registerGcMetrics store = - , ("rts.gc.par_max_bytes_copied" , Gauge . Stats.parMaxBytesCopied) - ]) - getGcStats -+#endif - store - -+#if MIN_VERSION_base(4,10,0) -+-- | Get RTS statistics. -+getRTSStats :: IO Stats.RTSStats -+getRTSStats = do -+ enabled <- Stats.getRTSStatsEnabled -+ if enabled -+ then Stats.getRTSStats -+ else return emptyRTSStats -+ -+-- | Empty RTS statistics, as if the application hasn't started yet. -+emptyRTSStats :: Stats.RTSStats -+emptyRTSStats = Stats.RTSStats -+ { gcs = 0 -+ , major_gcs = 0 -+ , allocated_bytes = 0 -+ , max_live_bytes = 0 -+ , max_large_objects_bytes = 0 -+ , max_compact_bytes = 0 -+ , max_slop_bytes = 0 -+ , max_mem_in_use_bytes = 0 -+ , cumulative_live_bytes = 0 -+ , copied_bytes = 0 -+ , par_copied_bytes = 0 -+ , cumulative_par_max_copied_bytes = 0 -+# if MIN_VERSION_base(4,11,0) -+ , cumulative_par_balanced_copied_bytes = 0 -+# endif -+ , mutator_cpu_ns = 0 -+ , mutator_elapsed_ns = 0 -+ , gc_cpu_ns = 0 -+ , gc_elapsed_ns = 0 -+ , cpu_ns = 0 -+ , elapsed_ns = 0 -+ , gc = emptyGCDetails -+ } -+ -+emptyGCDetails :: Stats.GCDetails -+emptyGCDetails = Stats.GCDetails -+ { gcdetails_gen = 0 -+ , gcdetails_threads = 0 -+ , gcdetails_allocated_bytes = 0 -+ , gcdetails_live_bytes = 0 -+ , gcdetails_large_objects_bytes = 0 -+ , gcdetails_compact_bytes = 0 -+ , gcdetails_slop_bytes = 0 -+ , gcdetails_mem_in_use_bytes = 0 -+ , gcdetails_copied_bytes = 0 -+ , gcdetails_par_max_copied_bytes = 0 -+# if MIN_VERSION_base(4,11,0) -+ , gcdetails_par_balanced_copied_bytes = 0 -+# endif -+ , gcdetails_sync_elapsed_ns = 0 -+ , gcdetails_cpu_ns = 0 -+ , gcdetails_elapsed_ns = 0 -+ } -+#else - -- | Get GC statistics. - getGcStats :: IO Stats.GCStats --#if MIN_VERSION_base(4,6,0) -+# if MIN_VERSION_base(4,6,0) - getGcStats = do - enabled <- Stats.getGCStatsEnabled - if enabled -@@ -445,7 +532,6 @@ getGcStats = do - - -- | Empty GC statistics, as if the application hasn't started yet. - emptyGCStats :: Stats.GCStats --# if MIN_VERSION_base(4,10,0) - emptyGCStats = Stats.GCStats - { bytesAllocated = 0 - , numGcs = 0 -@@ -465,40 +551,18 @@ emptyGCStats = Stats.GCStats - , wallSeconds = 0 - , parTotBytesCopied = 0 - , parMaxBytesCopied = 0 -- , mblocksAllocated = 0 - } - # else --emptyGCStats = Stats.GCStats -- { bytesAllocated = 0 -- , numGcs = 0 -- , maxBytesUsed = 0 -- , numByteUsageSamples = 0 -- , cumulativeBytesUsed = 0 -- , bytesCopied = 0 -- , currentBytesUsed = 0 -- , currentBytesSlop = 0 -- , maxBytesSlop = 0 -- , peakMegabytesAllocated = 0 -- , mutatorCpuSeconds = 0 -- , mutatorWallSeconds = 0 -- , gcCpuSeconds = 0 -- , gcWallSeconds = 0 -- , cpuSeconds = 0 -- , wallSeconds = 0 -- , parTotBytesCopied = 0 -- , parMaxBytesCopied = 0 -- } --# endif --#else - getGcStats = Stats.getGCStats --#endif -+# endif - - -- | Helper to work around rename in GHC.Stats in base-4.6. - gcParTotBytesCopied :: Stats.GCStats -> Int64 --#if MIN_VERSION_base(4,6,0) -+# if MIN_VERSION_base(4,6,0) - gcParTotBytesCopied = Stats.parTotBytesCopied --#else -+# else - gcParTotBytesCopied = Stats.parAvgBytesCopied -+# endif - #endif - - ------------------------------------------------------------------------ diff --git a/patches/entropy-0.4.1.1.patch b/patches/entropy-0.4.1.1.patch deleted file mode 100644 index f4b33d5de349f96b34b2105f3ca6e86cc2e63c8d..0000000000000000000000000000000000000000 --- a/patches/entropy-0.4.1.1.patch +++ /dev/null @@ -1,54 +0,0 @@ -commit e212bc7fba4b874234b5c901c98418cd9c0bfbac -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Mon May 7 16:17:34 2018 -0400 - - Allow building with unix-2.8 - -diff --git a/System/EntropyNix.hs b/System/EntropyNix.hs -index 01a7bc4..3f5bd5b 100644 ---- a/System/EntropyNix.hs -+++ b/System/EntropyNix.hs -@@ -64,7 +64,11 @@ openHandle :: IO CryptHandle - openHandle = do CH `fmap` nonRDRandHandle - where - nonRDRandHandle :: IO Fd -- nonRDRandHandle = openFd source ReadOnly Nothing defaultFileFlags -+ nonRDRandHandle = openFd source ReadOnly -+#if !(MIN_VERSION_unix(2,8,0)) -+ Nothing -+#endif -+ defaultFileFlags - - -- |Close the `CryptHandle` - closeHandle :: CryptHandle -> IO () - -commit c682fcd6cc2bcaa5cab9f6e59a93faf8c9938221 -Merge: 74fed23 fa82202 -Author: Thomas M. DuBuisson <thomas.dubuisson@gmail.com> -Date: Mon May 7 09:07:46 2018 -0700 - - Merge pull request #39 from RyanGlScott/master - - Use ghcProgram in Setup.hs script - - -commit fa822029cf7ae838dba8b9b6e2f51d897089ea50 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Mon May 7 09:55:43 2018 -0400 - - Use ghcProgram in Setup.hs script - -diff --git a/Setup.hs b/Setup.hs -index 49b693f..61f116a 100644 ---- a/Setup.hs -+++ b/Setup.hs -@@ -17,8 +17,7 @@ main = defaultMainWithHooks hk - where - hk = simpleUserHooks { buildHook = \pd lbi uh bf -> do - -- let ccProg = Program "gcc" undefined undefined undefined -- let hcProg = Program "ghc" undefined undefined undefined -- mConf = lookupProgram hcProg (withPrograms lbi) -+ let mConf = lookupProgram ghcProgram (withPrograms lbi) - err = error "Could not determine C compiler" - cc = locationPath . programLocation . maybe err id $ mConf - b <- canUseRDRAND cc diff --git a/patches/errors-2.2.2.patch b/patches/errors-2.2.2.patch deleted file mode 100644 index c1d70cc7f2faa6ae793f2de1dfdeae7540055d03..0000000000000000000000000000000000000000 --- a/patches/errors-2.2.2.patch +++ /dev/null @@ -1,65 +0,0 @@ -diff -ru errors-2.2.2.orig/Control/Error/Util.hs errors-2.2.2/Control/Error/Util.hs ---- errors-2.2.2.orig/Control/Error/Util.hs 2017-09-16 20:17:39.000000000 +0200 -+++ errors-2.2.2/Control/Error/Util.hs 2017-09-17 11:31:50.703875806 +0200 -@@ -1,3 +1,5 @@ -+{-# LANGUAGE CPP #-} -+ - -- | This module exports miscellaneous error-handling functions. - - module Control.Error.Util ( -@@ -60,6 +62,9 @@ - import Control.Monad.Trans.Maybe (MaybeT(MaybeT), runMaybeT) - import Data.Dynamic (Dynamic) - import Data.Monoid (Monoid(mempty, mappend)) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Data.Maybe (fromMaybe) - import Data.Text (Text) - import System.Exit (ExitCode) -@@ -197,12 +202,22 @@ - -} - newtype AllE e r = AllE { runAllE :: Either e r } - -+#if MIN_VERSION_base(4,9,0) -+instance (Semigroup e, Semigroup r) => Semigroup (AllE e r) where -+ AllE (Right x) <> AllE (Right y) = AllE (Right (x <> y)) -+ AllE (Right _) <> AllE (Left y) = AllE (Left y) -+ AllE (Left x) <> AllE (Right _) = AllE (Left x) -+ AllE (Left x) <> AllE (Left y) = AllE (Left (x <> y)) -+#endif -+ - instance (Monoid e, Monoid r) => Monoid (AllE e r) where - mempty = AllE (Right mempty) -+#if !(MIN_VERSION_base(4,11,0)) - mappend (AllE (Right x)) (AllE (Right y)) = AllE (Right (mappend x y)) - mappend (AllE (Right _)) (AllE (Left y)) = AllE (Left y) - mappend (AllE (Left x)) (AllE (Right _)) = AllE (Left x) - mappend (AllE (Left x)) (AllE (Left y)) = AllE (Left (mappend x y)) -+#endif - - {-| Run multiple 'Either' computations and succeed if any of them succeed - -@@ -210,12 +225,22 @@ - -} - newtype AnyE e r = AnyE { runAnyE :: Either e r } - -+#if MIN_VERSION_base(4,9,0) -+instance (Semigroup e, Semigroup r) => Semigroup (AnyE e r) where -+ AnyE (Right x) <> AnyE (Right y) = AnyE (Right (x <> y)) -+ AnyE (Right x) <> AnyE (Left _) = AnyE (Right x) -+ AnyE (Left _) <> AnyE (Right y) = AnyE (Right y) -+ AnyE (Left x) <> AnyE (Left y) = AnyE (Left (x <> y)) -+#endif -+ - instance (Monoid e, Monoid r) => Monoid (AnyE e r) where - mempty = AnyE (Right mempty) -+#if !(MIN_VERSION_base(4,11,0)) - mappend (AnyE (Right x)) (AnyE (Right y)) = AnyE (Right (mappend x y)) - mappend (AnyE (Right x)) (AnyE (Left _)) = AnyE (Right x) - mappend (AnyE (Left _)) (AnyE (Right y)) = AnyE (Right y) - mappend (AnyE (Left x)) (AnyE (Left y)) = AnyE (Left (mappend x y)) -+#endif - - -- | Analogous to 'isLeft', but for 'ExceptT' - isLeftT :: (Monad m) => ExceptT a m b -> m Bool diff --git a/patches/exact-pi-0.4.1.3.patch b/patches/exact-pi-0.4.1.3.patch deleted file mode 100644 index 80a9a99a34ca845f6f08562756f63be45497caa2..0000000000000000000000000000000000000000 --- a/patches/exact-pi-0.4.1.3.patch +++ /dev/null @@ -1,46 +0,0 @@ -diff -ru exact-pi-0.4.1.3.orig/src/Data/ExactPi/TypeLevel.hs exact-pi-0.4.1.3/src/Data/ExactPi/TypeLevel.hs ---- exact-pi-0.4.1.3.orig/src/Data/ExactPi/TypeLevel.hs 2018-01-30 16:41:26.000000000 -0500 -+++ exact-pi-0.4.1.3/src/Data/ExactPi/TypeLevel.hs 2018-07-09 10:39:23.714215253 -0400 -@@ -1,12 +1,16 @@ - {-# OPTIONS_HADDOCK show-extensions #-} - - {-# LANGUAGE ConstraintKinds #-} -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DataKinds #-} - {-# LANGUAGE FlexibleContexts #-} - {-# LANGUAGE KindSignatures #-} - {-# LANGUAGE ScopedTypeVariables #-} - {-# LANGUAGE TypeFamilies #-} - {-# LANGUAGE TypeOperators #-} -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - - {-| - Module : Data.ExactPi.TypeLevel -@@ -34,6 +38,7 @@ - where - - import Data.ExactPi -+import Data.Kind (Type) - import Data.Maybe (fromJust) - import Data.Proxy - import Data.Ratio -@@ -69,7 +74,7 @@ - - -- | Determines the minimum context required for a numeric type to hold the value - -- associated with a specific 'ExactPi'' type. --type family MinCtxt' (v :: ExactPi') :: * -> Constraint where -+type family MinCtxt' (v :: ExactPi') :: Type -> Constraint where - MinCtxt' ('ExactPi' 'Zero p 1) = Num - MinCtxt' ('ExactPi' 'Zero p q) = Fractional - MinCtxt' ('ExactPi' z p q) = Floating -@@ -78,7 +83,7 @@ - - -- | A KnownMinCtxt is a contraint on values sufficient to allow us to inject certain - -- 'ExactPi' values into types that satisfy the constraint. --class KnownMinCtxt (c :: * -> Constraint) where -+class KnownMinCtxt (c :: Type -> Constraint) where - -- | Injects an 'ExactPi' value into a specified type satisfying this constraint. - -- - -- The injection is permitted to fail if type constraint does not entail the 'MinCtxt' diff --git a/patches/fast-logger-2.4.10.patch b/patches/fast-logger-2.4.10.patch deleted file mode 100644 index b739876e10e9845c62679084c9f19bf1a46bc848..0000000000000000000000000000000000000000 --- a/patches/fast-logger-2.4.10.patch +++ /dev/null @@ -1,33 +0,0 @@ -From c4dba2ca9b9365bf4347102d2aa9e4c77d23b229 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sun, 4 Feb 2018 19:45:03 -0500 -Subject: [PATCH] Give an explicit definition for (<>) in LogStr's Semigroup - instance - ---- - System/Log/FastLogger/LogStr.hs | 5 +++-- - 1 file changed, 3 insertions(+), 2 deletions(-) - -diff --git a/System/Log/FastLogger/LogStr.hs b/System/Log/FastLogger/LogStr.hs -index 84ead40..b6f634d 100644 ---- a/System/Log/FastLogger/LogStr.hs -+++ b/System/Log/FastLogger/LogStr.hs -@@ -25,7 +25,7 @@ import Data.Monoid (Monoid, mempty, mappend) - import Data.Monoid ((<>)) - #endif - #if MIN_VERSION_base(4,9,0) --import Data.Semigroup (Semigroup) -+import qualified Data.Semigroup as Semi (Semigroup(..)) - #endif - import Data.String (IsString(..)) - import qualified Data.Text as T -@@ -56,7 +56,8 @@ fromBuilder = BS.concat . BL.toChunks . B.toLazyByteString - data LogStr = LogStr !Int Builder - - #if MIN_VERSION_base(4,9,0) --instance Semigroup LogStr -+instance Semi.Semigroup LogStr where -+ LogStr s1 b1 <> LogStr s2 b2 = LogStr (s1 + s2) (b1 <> b2) - #endif - - instance Monoid LogStr where diff --git a/patches/fingertree-0.1.1.0.patch b/patches/fingertree-0.1.1.0.patch deleted file mode 100644 index 2335123005a72d155e2dd5637bb7edb830e4933b..0000000000000000000000000000000000000000 --- a/patches/fingertree-0.1.1.0.patch +++ /dev/null @@ -1,145 +0,0 @@ -diff -ru fingertree-0.1.1.0.orig/Data/FingerTree.hs fingertree-0.1.1.0/Data/FingerTree.hs ---- fingertree-0.1.1.0.orig/Data/FingerTree.hs 2015-06-09 13:26:48.000000000 +0200 -+++ fingertree-0.1.1.0/Data/FingerTree.hs 2017-09-17 10:32:22.555868451 +0200 -@@ -64,6 +64,12 @@ - - import Control.Applicative (Applicative(pure, (<*>)), (<$>)) - import Data.Monoid -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Data.Foldable (Foldable(foldMap), toList) - - infixr 5 >< -@@ -91,10 +97,18 @@ - fmap _ EmptyR = EmptyR - fmap f (xs :> x) = fmap f xs :> f x - -+#if MIN_VERSION_base(4,9,0) -+instance (Measured v a) => Semigroup (FingerTree v a) where -+ (<>) = (><) -+#endif -+ - -- | 'empty' and '><'. - instance Measured v a => Monoid (FingerTree v a) where - mempty = empty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = (><) -+#endif -+ - - -- Explicit Digit type (Exercise 1) - -diff -ru fingertree-0.1.1.0.orig/Data/IntervalMap/FingerTree.hs fingertree-0.1.1.0/Data/IntervalMap/FingerTree.hs ---- fingertree-0.1.1.0.orig/Data/IntervalMap/FingerTree.hs 2015-06-09 13:26:48.000000000 +0200 -+++ fingertree-0.1.1.0/Data/IntervalMap/FingerTree.hs 2017-09-17 09:07:17.097589571 +0200 -@@ -77,12 +77,23 @@ - -- rightmost interval (including largest lower bound) and largest upper bound. - data IntInterval v = NoInterval | IntInterval (Interval v) v - -+#if MIN_VERSION_base(4,9,0) -+instance Ord v => Semigroup (IntInterval v) where -+ (<>) = intervalUnion -+#endif -+ - instance Ord v => Monoid (IntInterval v) where - mempty = NoInterval -- NoInterval `mappend` i = i -- i `mappend` NoInterval = i -- IntInterval _ hi1 `mappend` IntInterval int2 hi2 = -- IntInterval int2 (max hi1 hi2) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = intervalUnion -+#endif -+ -+intervalUnion :: Ord v => IntInterval v -> IntInterval v -> IntInterval v -+NoInterval `intervalUnion` i = i -+i `intervalUnion` NoInterval = i -+IntInterval _ hi1 `intervalUnion` IntInterval int2 hi2 = -+ IntInterval int2 (max hi1 hi2) -+ - - instance (Ord v) => Measured (IntInterval v) (Node v a) where - measure (Node i _) = IntInterval i (high i) -@@ -104,10 +115,18 @@ - traverse f (IntervalMap t) = - IntervalMap <$> FT.unsafeTraverse (traverse f) t - -+#if MIN_VERSION_base(4,9,0) -+-- | 'union'. -+instance (Ord v) => Semigroup (IntervalMap v a) where -+ (<>) = union -+#endif -+ - -- | 'empty' and 'union'. - instance (Ord v) => Monoid (IntervalMap v a) where - mempty = empty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = union -+#endif - - -- | /O(1)/. The empty interval map. - empty :: (Ord v) => IntervalMap v a -diff -ru fingertree-0.1.1.0.orig/Data/PriorityQueue/FingerTree.hs fingertree-0.1.1.0/Data/PriorityQueue/FingerTree.hs ---- fingertree-0.1.1.0.orig/Data/PriorityQueue/FingerTree.hs 2015-06-09 13:26:48.000000000 +0200 -+++ fingertree-0.1.1.0/Data/PriorityQueue/FingerTree.hs 2017-09-17 10:33:39.103399420 +0200 -@@ -60,6 +60,9 @@ - import Control.Arrow ((***)) - import Data.Foldable (Foldable(foldMap)) - import Data.Monoid -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Prelude hiding (null) - - data Entry k v = Entry k v -@@ -72,13 +75,23 @@ - - data Prio k v = NoPrio | Prio k v - -+#if MIN_VERSION_base(4,9,0) -+instance Ord k => Semigroup (Prio k v) where -+ (<>) = unionPrio -+#endif -+ - instance Ord k => Monoid (Prio k v) where -- mempty = NoPrio -- x `mappend` NoPrio = x -- NoPrio `mappend` y = y -- x@(Prio kx _) `mappend` y@(Prio ky _) -- | kx <= ky = x -- | otherwise = y -+ mempty = NoPrio -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = unionPrio -+#endif -+ -+unionPrio :: Ord k => Prio k v -> Prio k v -> Prio k v -+x `unionPrio` NoPrio = x -+NoPrio `unionPrio` y = y -+x@(Prio kx _) `unionPrio` y@(Prio ky _) -+ | kx <= ky = x -+ | otherwise = y - - instance Ord k => Measured (Prio k v) (Entry k v) where - measure (Entry k v) = Prio k v -@@ -94,9 +107,16 @@ - Nothing -> mempty - Just (v, q') -> f v `mappend` foldMap f q' - -+#if MIN_VERSION_base(4,9,0) -+instance Ord k => Semigroup (PQueue k v) where -+ (<>) = union -+#endif -+ - instance Ord k => Monoid (PQueue k v) where - mempty = empty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = union -+#endif - - -- | /O(1)/. The empty priority queue. - empty :: Ord k => PQueue k v diff --git a/patches/flat-0.3.2.patch b/patches/flat-0.3.2.patch deleted file mode 100644 index d3fbb4252f90d70c8e2f1c51d2d0248769da2c14..0000000000000000000000000000000000000000 --- a/patches/flat-0.3.2.patch +++ /dev/null @@ -1,28 +0,0 @@ -diff --git a/src/Data/Flat/Class.hs b/src/Data/Flat/Class.hs -index d982b039..bcae82d8 100644 ---- a/src/Data/Flat/Class.hs -+++ b/src/Data/Flat/Class.hs -@@ -28,7 +28,7 @@ import Data.Flat.Decoder (Get, dBool) - import Data.Flat.Encoder - import Data.Proxy - import GHC.Generics --import GHC.TypeLits -+import GHC.TypeLits as Lits - import Prelude hiding (mempty) - -- import GHC.Magic(inline) - -@@ -142,11 +142,11 @@ class (KnownNat code, KnownNat numBits) => - GEncodeSum (numBits:: Nat) (code :: Nat) (f :: * -> *) where - gencodeSum :: f a -> Proxy numBits -> Proxy code -> Encoding - --instance (GEncodeSum (n+1) (m*2) a,GEncodeSum (n+1) (m*2+1) b, KnownNat n,KnownNat m) -+instance (KnownNat n,KnownNat m,GEncodeSum (n+1) (m Lits.* 2) a,GEncodeSum (n+1) ((m Lits.* 2)+1) b) - => GEncodeSum n m (a :+: b) where - gencodeSum !x _ _ = case x of -- L1 l -> gencodeSum l (Proxy :: Proxy (n+1)) (Proxy :: Proxy (m*2)) -- R1 r -> gencodeSum r (Proxy :: Proxy (n+1)) (Proxy :: Proxy (m*2+1)) -+ L1 l -> gencodeSum l (Proxy :: Proxy (n+1)) (Proxy :: Proxy (m Lits.* 2)) -+ R1 r -> gencodeSum r (Proxy :: Proxy (n+1)) (Proxy :: Proxy (m Lits.* 2+1)) - {-# INLINE gencodeSum #-} - - instance (GEncoders a, KnownNat n,KnownNat m) => GEncodeSum n m (C1 c a) where diff --git a/patches/fmlist-0.9.patch b/patches/fmlist-0.9.patch deleted file mode 100644 index a8c237b79c714c9cddcce157bb22976a8274d5bc..0000000000000000000000000000000000000000 --- a/patches/fmlist-0.9.patch +++ /dev/null @@ -1,43 +0,0 @@ -diff -ru fmlist-0.9.orig/Data/FMList.hs fmlist-0.9/Data/FMList.hs ---- fmlist-0.9.orig/Data/FMList.hs 2015-01-02 11:46:31.000000000 +0100 -+++ fmlist-0.9/Data/FMList.hs 2017-09-17 11:03:22.769360899 +0200 -@@ -87,7 +87,8 @@ - , Show(..), String, (++) - ) - import Data.Maybe (Maybe(..), maybe, fromMaybe, isNothing) --import Data.Monoid -+import qualified Data.Semigroup as Semigroup -+import Data.Monoid hiding ((<>)) - import Data.Foldable (Foldable, foldMap, foldr, toList) - import Data.Traversable (Traversable, traverse) - import Control.Monad -@@ -256,9 +257,13 @@ - - - newtype WrapApp f m = WrapApp { unWrapApp :: f m } -+ -+instance (Applicative f, Semigroup.Semigroup m) => Semigroup.Semigroup (WrapApp f m) where -+ WrapApp a <> WrapApp b = WrapApp $ (Semigroup.<>) <$> a <*> b -+ - instance (Applicative f, Monoid m) => Monoid (WrapApp f m) where - mempty = WrapApp $ pure mempty -- mappend (WrapApp a) (WrapApp b) = WrapApp $ mappend <$> a <*> b -+ mappend = (Semigroup.<>) - - -- | Map each element of a structure to an action, evaluate these actions from left to right, - -- and concat the monoid results. -@@ -289,9 +294,12 @@ - as <* bs = transform (\f a -> unFM bs (const (f a))) as - as *> bs = transform (\f -> const (unFM bs f)) as - -+instance Semigroup.Semigroup (FMList a) where -+ (<>) = (><) -+ - instance Monoid (FMList a) where - mempty = nil -- mappend = (><) -+ mappend = (Semigroup.<>) - - instance MonadPlus FMList where - mzero = nil -Only in fmlist-0.9/Data: FMList.hs~ diff --git a/patches/foldl-1.3.1.patch b/patches/foldl-1.3.1.patch deleted file mode 100644 index a431308dc679b78796b1bc296b9644254805fcd3..0000000000000000000000000000000000000000 --- a/patches/foldl-1.3.1.patch +++ /dev/null @@ -1,57 +0,0 @@ -diff -ru foldl-1.3.1.orig/src/Control/Foldl.hs foldl-1.3.1/src/Control/Foldl.hs ---- foldl-1.3.1.orig/src/Control/Foldl.hs 2017-09-03 04:12:45.000000000 +0200 -+++ foldl-1.3.1/src/Control/Foldl.hs 2017-09-14 22:41:32.877465396 +0200 -@@ -144,6 +144,7 @@ - import Data.Functor.Identity (Identity, runIdentity) - import Data.Functor.Contravariant (Contravariant(..)) - import Data.Monoid -+import Data.Semigroup (Semigroup(..)) - import Data.Profunctor - import Data.Sequence ((|>)) - import Data.Vector.Generic (Vector, Mutable) -@@ -222,11 +223,15 @@ - in Fold step begin done - {-# INLINE (<*>) #-} - -+instance Monoid b => Semigroup (Fold a b) where -+ (<>) = liftA2 mappend -+ {-# INLINE (<>) #-} -+ - instance Monoid b => Monoid (Fold a b) where - mempty = pure mempty - {-# INLINE mempty #-} - -- mappend = liftA2 mappend -+ mappend = (<>) - {-# INLINE mappend #-} - - instance Num b => Num (Fold a b) where -@@ -357,6 +362,10 @@ - rmap = fmap - lmap = premapM - -+instance (Monoid b, Monad m) => Semigroup (FoldM m a b) where -+ (<>) = liftA2 mappend -+ {-# INLINE (<>) #-} -+ - instance (Monoid b, Monad m) => Monoid (FoldM m a b) where - mempty = pure mempty - {-# INLINE mempty #-} -@@ -1156,11 +1165,15 @@ - -} - newtype EndoM m a = EndoM { appEndoM :: a -> m a } - -+instance Monad m => Semigroup (EndoM m a) where -+ (EndoM f) <> (EndoM g) = EndoM (f <=< g) -+ {-# INLINE (<>) #-} -+ - instance Monad m => Monoid (EndoM m a) where - mempty = EndoM return - {-# INLINE mempty #-} - -- mappend (EndoM f) (EndoM g) = EndoM (f <=< g) -+ mappend = (<>) - {-# INLINE mappend #-} - - {-| A Handler for the upstream input of `FoldM` -Only in foldl-1.3.1/src/Control: Foldl.hs~ diff --git a/patches/formatting-6.3.0.patch b/patches/formatting-6.3.0.patch deleted file mode 100644 index 9daceca9384950d0ad71298995ab5b720204e7cb..0000000000000000000000000000000000000000 --- a/patches/formatting-6.3.0.patch +++ /dev/null @@ -1,99 +0,0 @@ -diff -ru formatting-6.3.0.orig/formatting.cabal formatting-6.3.0/formatting.cabal ---- formatting-6.3.0.orig/formatting.cabal 2017-12-20 14:13:42.000000000 +0000 -+++ formatting-6.3.0/formatting.cabal 2018-02-08 11:14:40.098204393 +0000 -@@ -42,7 +42,9 @@ - transformers, - bytestring, - integer-gmp >= 0.2 -- -+ if !impl(ghc >= 8.0) -+ build-depends: -+ semigroups >= 0.11 && < 0.19 - hs-source-dirs: src - ghc-options: -O2 - cpp-options: -DINTEGER_GMP -Only in formatting-6.3.0: ghc-8_4.patch -diff -ru formatting-6.3.0.orig/src/Data/Text/Format/Functions.hs formatting-6.3.0/src/Data/Text/Format/Functions.hs ---- formatting-6.3.0.orig/src/Data/Text/Format/Functions.hs 2017-12-20 13:43:07.000000000 +0000 -+++ formatting-6.3.0/src/Data/Text/Format/Functions.hs 2018-02-08 11:14:40.098204393 +0000 -@@ -1,4 +1,5 @@ - {-# LANGUAGE MagicHash #-} -+{-# LANGUAGE CPP #-} - - -- | - -- Module : Data.Text.Format.Functions -@@ -19,7 +20,12 @@ - - import Data.Monoid (mappend) - import Data.Text.Lazy.Builder (Builder) -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ((<>)) -+import GHC.Base hiding ((<>)) -+#else - import GHC.Base -+#endif - - -- | Unsafe conversion for decimal digits. - {-# INLINE i2d #-} -diff -ru formatting-6.3.0.orig/src/Data/Text/Format/Int.hs formatting-6.3.0/src/Data/Text/Format/Int.hs ---- formatting-6.3.0.orig/src/Data/Text/Format/Int.hs 2017-12-20 13:43:07.000000000 +0000 -+++ formatting-6.3.0/src/Data/Text/Format/Int.hs 2018-02-08 11:14:40.098204393 +0000 -@@ -17,6 +17,9 @@ - , minus - ) where - -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ((<>)) -+#endif - import Data.Int (Int8, Int16, Int32, Int64) - import Data.Monoid (mempty) - import Data.Text.Format.Functions ((<>), i2d) -diff -ru formatting-6.3.0.orig/src/Formatting/Buildable.hs formatting-6.3.0/src/Formatting/Buildable.hs ---- formatting-6.3.0.orig/src/Formatting/Buildable.hs 2017-12-20 13:43:07.000000000 +0000 -+++ formatting-6.3.0/src/Formatting/Buildable.hs 2018-02-08 11:14:40.098204393 +0000 -@@ -20,6 +20,9 @@ - import qualified Data.ByteString.Lazy as L - import Data.Void (Void, absurd) - #endif -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ((<>)) -+#endif - - import Data.Monoid (mempty) - import Data.Int (Int8, Int16, Int32, Int64) -diff -ru formatting-6.3.0.orig/src/Formatting/Internal.hs formatting-6.3.0/src/Formatting/Internal.hs ---- formatting-6.3.0.orig/src/Formatting/Internal.hs 2017-12-20 11:43:50.000000000 +0000 -+++ formatting-6.3.0/src/Formatting/Internal.hs 2018-02-08 11:14:40.098204393 +0000 -@@ -1,12 +1,16 @@ - {-# LANGUAGE GADTs #-} - {-# LANGUAGE FlexibleInstances #-} -+{-# LANGUAGE CPP #-} - - -- | Internal format starters. - - module Formatting.Internal where - - import Control.Category (Category(..)) -+import qualified Data.Semigroup as Sem -+#if !MIN_VERSION_base(4,11,0) - import Data.Monoid -+#endif - import Data.String - import qualified Data.Text as S (Text) - import Data.Text.Lazy (Text) -@@ -50,10 +54,13 @@ - -- | Useful instance for applying two formatters to the same input - -- argument. For example: @format (year <> "/" % month) now@ will - -- yield @"2015/01"@. --instance Monoid (Format r (a -> r)) where -- mappend m n = -+instance Sem.Semigroup (Format r (a -> r)) where -+ (<>) m n = - Format (\k a -> - runFormat m (\b1 -> runFormat n (\b2 -> k (b1 <> b2)) a) a) -+ -+instance Monoid (Format r (a -> r)) where -+ mappend = (<>) - mempty = Format (\k _ -> k mempty) - - -- | Useful instance for writing format string. With this you can diff --git a/patches/foundation-0.0.15.patch b/patches/foundation-0.0.15.patch deleted file mode 100644 index 7ce2ece516bf0f0961c49e852f42c279949665fb..0000000000000000000000000000000000000000 --- a/patches/foundation-0.0.15.patch +++ /dev/null @@ -1,129 +0,0 @@ -diff -ru foundation-0.0.15.orig/Foundation/Array/Bitmap.hs foundation-0.0.15/Foundation/Array/Bitmap.hs ---- foundation-0.0.15.orig/Foundation/Array/Bitmap.hs 2017-08-26 07:35:24.000000000 +0200 -+++ foundation-0.0.15/Foundation/Array/Bitmap.hs 2017-09-15 12:09:21.009784402 +0200 -@@ -43,6 +43,7 @@ - import Foundation.Bits - import GHC.ST - import qualified Data.List -+import Data.Semigroup - - data Bitmap = Bitmap (CountOf Bool) (UArray Word32) - -@@ -63,9 +64,13 @@ - (==) = equal - instance Ord Bitmap where - compare = vCompare -+ -+instance Semigroup Bitmap where -+ (<>) = append -+ - instance Monoid Bitmap where - mempty = empty -- mappend = append -+ mappend = (<>) - mconcat = concat - - type instance C.Element Bitmap = Bool -Only in foundation-0.0.15/Foundation/Array: Bitmap.hs~ -diff -ru foundation-0.0.15.orig/Foundation/Array/Chunked/Unboxed.hs foundation-0.0.15/Foundation/Array/Chunked/Unboxed.hs ---- foundation-0.0.15.orig/Foundation/Array/Chunked/Unboxed.hs 2017-08-26 07:35:24.000000000 +0200 -+++ foundation-0.0.15/Foundation/Array/Chunked/Unboxed.hs 2017-09-15 12:10:04.481538992 +0200 -@@ -32,7 +32,7 @@ - import Foundation.Numerical - import Foundation.Primitive - import qualified Foundation.Collection as C -- -+import Data.Semigroup - - newtype ChunkedUArray ty = ChunkedUArray (Array (UArray ty)) - deriving (Show, Ord, Typeable) -@@ -42,9 +42,12 @@ - instance NormalForm (ChunkedUArray ty) where - toNormalForm (ChunkedUArray spine) = toNormalForm spine - -+instance Semigroup (ChunkedUArray a) where -+ (<>) = append -+ - instance Monoid (ChunkedUArray a) where - mempty = empty -- mappend = append -+ mappend = (<>) - mconcat = concat - - type instance C.Element (ChunkedUArray ty) = ty -Only in foundation-0.0.15/Foundation/Array/Chunked: Unboxed.hs~ -diff -ru foundation-0.0.15.orig/Foundation/List/DList.hs foundation-0.0.15/Foundation/List/DList.hs ---- foundation-0.0.15.orig/Foundation/List/DList.hs 2017-09-03 10:51:08.000000000 +0200 -+++ foundation-0.0.15/Foundation/List/DList.hs 2017-09-15 12:08:51.737949839 +0200 -@@ -14,6 +14,7 @@ - import Basement.Compat.Base - import Foundation.Collection - import Basement.Compat.Bifunctor -+import Data.Semigroup - - newtype DList a = DList { unDList :: [a] -> [a] } - deriving (Typeable) -@@ -32,9 +33,12 @@ - fromList = DList . (<>) - toList = flip unDList [] - -+instance Semigroup (DList a) where -+ dl1 <> dl2 = DList $ unDList dl1 . unDList dl2 -+ - instance Monoid (DList a) where - mempty = DList id -- mappend dl1 dl2 = DList $ unDList dl1 . unDList dl2 -+ mappend = (<>) - - instance Functor DList where - fmap f = foldr (cons . f) mempty -Only in foundation-0.0.15/Foundation/List: DList.hs~ -diff -ru foundation-0.0.15.orig/Foundation/String/Builder.hs foundation-0.0.15/Foundation/String/Builder.hs ---- foundation-0.0.15.orig/Foundation/String/Builder.hs 2017-08-05 12:49:52.000000000 +0200 -+++ foundation-0.0.15/Foundation/String/Builder.hs 2017-09-15 12:10:28.845402633 +0200 -@@ -20,18 +20,19 @@ - --import Basement.Compat.Semigroup - import Basement.String (String) - import qualified Basement.String as S -+import Data.Semigroup - - data Builder = E String | T [Builder] - - instance IsString Builder where - fromString = E . fromString - ----instance Semigroup Builder where ---- (<>) = append -+instance Semigroup Builder where -+ (<>) = append - - instance Monoid Builder where - mempty = empty -- mappend = append -+ mappend = (<>) - mconcat = concat - - empty :: Builder -Only in foundation-0.0.15/Foundation/String: Builder.hs~ -diff -ru foundation-0.0.15.orig/Foundation/VFS/FilePath.hs foundation-0.0.15/Foundation/VFS/FilePath.hs ---- foundation-0.0.15.orig/Foundation/VFS/FilePath.hs 2017-08-05 12:49:52.000000000 +0200 -+++ foundation-0.0.15/Foundation/VFS/FilePath.hs 2017-09-15 12:11:04.621202371 +0200 -@@ -39,6 +39,7 @@ - import Foundation.Array - import Foundation.String (Encoding(..), ValidationFailure, toBytes, fromBytes, String) - import Foundation.VFS.Path(Path(..)) -+import Data.Semigroup - - import qualified Data.List - -- ------------------------------------------------------------------------- -- -@@ -184,6 +185,9 @@ - hasContigueSeparators (x1:x2:xs) = - (isSeparator x1 && x1 == x2) || hasContigueSeparators xs - -+instance Semigroup FileName where -+ (FileName a) <> (FileName b) = FileName $ a `mappend` b -+ - instance Monoid FileName where - mempty = FileName mempty - mappend (FileName a) (FileName b) = FileName $ a `mappend` b -Only in foundation-0.0.15/Foundation/VFS: FilePath.hs~ diff --git a/patches/free-4.12.4.patch b/patches/free-4.12.4.patch deleted file mode 100644 index 7544cc0a595484ea21bb360620178077e3da5d3d..0000000000000000000000000000000000000000 --- a/patches/free-4.12.4.patch +++ /dev/null @@ -1,148 +0,0 @@ -Only in free-4.12.4: dist-newstyle -diff -ru free-4.12.4.0/free.cabal free-4.12.4/free.cabal ---- free-4.12.4.0/free.cabal 2017-09-14 17:19:06.315447212 +0200 -+++ free-4.12.4/free.cabal 2017-09-14 17:19:35.291284981 +0200 -@@ -101,3 +101,9 @@ - Control.Monad.Trans.Iter - - ghc-options: -Wall -+ -+ -- See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0#base-4.9.0.0 -+ if impl(ghc >= 8.0) -+ ghc-options: -Wcompat -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances -+ else -+ build-depends: fail == 4.9.* -Only in free-4.12.4: .ghc.environment.x86_64-linux-8.2.1 -diff -ru free-4.12.4.0/src/Control/Alternative/Free/Final.hs free-4.12.4/src/Control/Alternative/Free/Final.hs ---- free-4.12.4.0/src/Control/Alternative/Free/Final.hs 2016-01-17 03:15:13.000000000 +0100 -+++ free-4.12.4/src/Control/Alternative/Free/Final.hs 2017-09-14 17:19:35.291284981 +0200 -@@ -49,7 +49,7 @@ - - instance Monoid (Alt f a) where - mempty = empty -- mappend = (<|>) -+ mappend = (<>) - - -- | A version of 'lift' that can be used with @f@. - liftAlt :: f a -> Alt f a -diff -ru free-4.12.4.0/src/Control/Alternative/Free.hs free-4.12.4/src/Control/Alternative/Free.hs ---- free-4.12.4.0/src/Control/Alternative/Free.hs 2016-01-17 03:15:13.000000000 +0100 -+++ free-4.12.4/src/Control/Alternative/Free.hs 2017-09-14 17:19:35.291284981 +0200 -@@ -117,7 +117,7 @@ - instance (Functor f) => Monoid (Alt f a) where - mempty = empty - {-# INLINE mempty #-} -- mappend = (<|>) -+ mappend = (<>) - {-# INLINE mappend #-} - mconcat as = Alt (as >>= alternatives) - {-# INLINE mconcat #-} -diff -ru free-4.12.4.0/src/Control/Monad/Trans/Free.hs free-4.12.4/src/Control/Monad/Trans/Free.hs ---- free-4.12.4.0/src/Control/Monad/Trans/Free.hs 2016-01-17 03:15:13.000000000 +0100 -+++ free-4.12.4/src/Control/Monad/Trans/Free.hs 2017-09-14 17:19:35.291284981 +0200 -@@ -62,6 +62,7 @@ - import Control.Monad.Catch (MonadThrow(..), MonadCatch(..)) - import Control.Monad.Trans.Class - import Control.Monad.Free.Class -+import qualified Control.Monad.Fail as Fail - import Control.Monad.IO.Class - import Control.Monad.Reader.Class - import Control.Monad.Writer.Class -@@ -223,13 +224,17 @@ - (>>-) = (>>=) - - instance (Functor f, Monad m) => Monad (FreeT f m) where -- fail e = FreeT (fail e) - return = pure - {-# INLINE return #-} - FreeT m >>= f = FreeT $ m >>= \v -> case v of - Pure a -> runFreeT (f a) - Free w -> return (Free (fmap (>>= f) w)) - -+ fail = Fail.fail -+ -+instance (Functor f, Monad m) => Fail.MonadFail (FreeT f m) where -+ fail e = FreeT (fail e) -+ - instance MonadTrans (FreeT f) where - lift = FreeT . liftM Pure - {-# INLINE lift #-} -diff -ru free-4.12.4.0/src/Control/Monad/Trans/Iter.hs free-4.12.4/src/Control/Monad/Trans/Iter.hs ---- free-4.12.4.0/src/Control/Monad/Trans/Iter.hs 2016-01-17 03:15:13.000000000 +0100 -+++ free-4.12.4/src/Control/Monad/Trans/Iter.hs 2017-09-14 17:21:25.950665537 +0200 -@@ -81,6 +81,7 @@ - import Control.Monad (ap, liftM, MonadPlus(..), join) - import Control.Monad.Fix - import Control.Monad.Trans.Class -+import qualified Control.Monad.Fail as Fail - import Control.Monad.Free.Class - import Control.Monad.State.Class - import Control.Monad.Error.Class -@@ -94,7 +95,7 @@ - import Data.Functor.Bind hiding (join) - import Data.Functor.Identity - import Data.Function (on) --import Data.Monoid -+import Data.Semigroup - import Data.Semigroup.Foldable - import Data.Semigroup.Traversable - import Data.Typeable -@@ -176,6 +177,10 @@ - {-# INLINE return #-} - IterT m >>= k = IterT $ m >>= either (runIterT . k) (return . Right . (>>= k)) - {-# INLINE (>>=) #-} -+ fail = Fail.fail -+ {-# INLINE fail #-} -+ -+instance Monad m => Fail.MonadFail (IterT m) where - fail _ = never - {-# INLINE fail #-} - -@@ -240,7 +245,7 @@ - listen (IterT m) = IterT $ liftM concat' $ listen (fmap listen `liftM` m) - where - concat' (Left x, w) = Left (x, w) -- concat' (Right y, w) = Right $ second (w <>) <$> y -+ concat' (Right y, w) = Right $ second (w `mappend`) <$> y - pass m = IterT . pass' . runIterT . hoistIterT clean $ listen m - where - clean = pass . liftM (\x -> (x, const mempty)) -@@ -388,17 +393,9 @@ - interleave_ xs = IterT $ liftM (Right . interleave_ . rights) $ mapM runIterT xs - {-# INLINE interleave_ #-} - --instance (Monad m, Monoid a) => Monoid (IterT m a) where -+instance (Monad m, Semigroup a, Monoid a) => Monoid (IterT m a) where - mempty = return mempty -- x `mappend` y = IterT $ do -- x' <- runIterT x -- y' <- runIterT y -- case (x', y') of -- ( Left a, Left b) -> return . Left $ a `mappend` b -- ( Left a, Right b) -> return . Right $ liftM (a `mappend`) b -- (Right a, Left b) -> return . Right $ liftM (`mappend` b) a -- (Right a, Right b) -> return . Right $ a `mappend` b -- -+ mappend = (<>) - mconcat = mconcat' . map Right - where - mconcat' :: (Monad m, Monoid a) => [Either a (IterT m a)] -> IterT m a -@@ -416,7 +413,17 @@ - - compact' a [] = [Left a] - compact' a (r@(Right _):xs) = (Left a):(r:(compact xs)) -- compact' a ( (Left a'):xs) = compact' (a <> a') xs -+ compact' a ( (Left a'):xs) = compact' (a `mappend` a') xs -+ -+instance (Monad m, Semigroup a) => Semigroup (IterT m a) where -+ x <> y = IterT $ do -+ x' <- runIterT x -+ y' <- runIterT y -+ case (x', y') of -+ ( Left a, Left b) -> return . Left $ a <> b -+ ( Left a, Right b) -> return . Right $ liftM (a <>) b -+ (Right a, Left b) -> return . Right $ liftM (<> b) a -+ (Right a, Right b) -> return . Right $ a <> b - - #if __GLASGOW_HASKELL__ < 707 - instance Typeable1 m => Typeable1 (IterT m) where diff --git a/patches/gloss-rendering-1.11.1.1.patch b/patches/gloss-rendering-1.11.1.1.patch deleted file mode 100644 index 71d6ea24551d8a48778e90434fc3b402a046e150..0000000000000000000000000000000000000000 --- a/patches/gloss-rendering-1.11.1.1.patch +++ /dev/null @@ -1,57 +0,0 @@ -diff -ru gloss-rendering-1.11.1.1.orig/gloss-rendering.cabal gloss-rendering-1.11.1.1/gloss-rendering.cabal ---- gloss-rendering-1.11.1.1.orig/gloss-rendering.cabal 2017-03-14 04:24:47.000000000 +0100 -+++ gloss-rendering-1.11.1.1/gloss-rendering.cabal 2018-01-09 14:24:04.731122386 +0100 -@@ -17,7 +17,7 @@ - exposed-modules: - Graphics.Gloss.Rendering - -- other-modules: -+ other-modules: - Graphics.Gloss.Internals.Data.Color - Graphics.Gloss.Internals.Data.Picture - Graphics.Gloss.Internals.Rendering.Bitmap -@@ -27,13 +27,14 @@ - Graphics.Gloss.Internals.Rendering.Picture - Graphics.Gloss.Internals.Rendering.State - -- build-depends: -- base >= 4.8 && < 4.10, -+ build-depends: -+ base >= 4.8 && < 4.11, - containers == 0.5.*, - bytestring == 0.10.*, - OpenGL >= 2.12 && < 3.1, - GLUT == 2.7.*, -- bmp == 1.2.* -+ bmp == 1.2.*, -+ semigroups >= 0.16 && < 0.19 - - ghc-options: - -Wall -O2 -diff -ru gloss-rendering-1.11.1.1.orig/Graphics/Gloss/Internals/Data/Picture.hs gloss-rendering-1.11.1.1/Graphics/Gloss/Internals/Data/Picture.hs ---- gloss-rendering-1.11.1.1.orig/Graphics/Gloss/Internals/Data/Picture.hs 2017-03-14 04:24:47.000000000 +0100 -+++ gloss-rendering-1.11.1.1/Graphics/Gloss/Internals/Data/Picture.hs 2018-01-09 14:21:44.947973336 +0100 -@@ -23,7 +23,8 @@ - import Foreign.Marshal.Utils - import Foreign.Ptr - import Data.Word --import Data.Monoid -+import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.ByteString - import Data.Data - import System.IO.Unsafe -@@ -125,9 +126,12 @@ - - - -- Instances ------------------------------------------------------------------ -+instance Semigroup Picture where -+ a <> b = Pictures [a, b] -+ - instance Monoid Picture where - mempty = Blank -- mappend a b = Pictures [a, b] -+ mappend = (<>) - mconcat = Pictures - - diff --git a/patches/gtk2hs-buildtools-0.13.3.1.patch b/patches/gtk2hs-buildtools-0.13.3.1.patch deleted file mode 100644 index 4795d5cf8c2fee28726b9f477f87279dbe7df804..0000000000000000000000000000000000000000 --- a/patches/gtk2hs-buildtools-0.13.3.1.patch +++ /dev/null @@ -1,36 +0,0 @@ -diff -ru gtk2hs-buildtools-0.13.3.1.orig/c2hs/c/CPretty.hs gtk2hs-buildtools-0.13.3.1/c2hs/c/CPretty.hs ---- gtk2hs-buildtools-0.13.3.1.orig/c2hs/c/CPretty.hs 2017-11-25 18:58:05.000000000 -0500 -+++ gtk2hs-buildtools-0.13.3.1/c2hs/c/CPretty.hs 2018-02-26 12:06:21.956401282 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - -- C->Haskell Compiler: pretty printing of C abstract syntax - -- - -- Author : Manuel M T Chakravarty -@@ -34,6 +35,9 @@ - -- we are just providing instances to the class `Pretty' - ) where - -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ((<>)) -+#endif - import Idents (Ident, identToLexeme) - import Text.PrettyPrint.HughesPJ - -diff -ru gtk2hs-buildtools-0.13.3.1.orig/gtk2hs-buildtools.cabal gtk2hs-buildtools-0.13.3.1/gtk2hs-buildtools.cabal ---- gtk2hs-buildtools-0.13.3.1.orig/gtk2hs-buildtools.cabal 2017-11-25 18:58:05.000000000 -0500 -+++ gtk2hs-buildtools-0.13.3.1/gtk2hs-buildtools.cabal 2018-02-26 12:06:21.956401282 -0500 -@@ -40,10 +40,10 @@ - build-depends: base >= 4 && < 5, - process, array, pretty, - filepath, random, -- Cabal >= 1.24.0.0 && < 2.1, -- filepath >= 1.3.0.0 && < 1.5, -- directory >= 1.2.0.0 && < 1.4, -- containers >= 0.5.5.1 && < 0.6 -+ Cabal >= 1.24.0.0, -+ filepath >= 1.3.0.0, -+ directory >= 1.2.0.0, -+ containers >= 0.5.5.1 - if impl(ghc >= 7.7) - build-depends: hashtables - build-tools: alex >= 3.0.1, happy >= 1.18.9 diff --git a/patches/hackage-security-0.5.2.2.patch b/patches/hackage-security-0.5.2.2.patch deleted file mode 100644 index bb4eb49452baea13f470506ad1b921859b1283ca..0000000000000000000000000000000000000000 --- a/patches/hackage-security-0.5.2.2.patch +++ /dev/null @@ -1,526 +0,0 @@ -diff -ru hackage-security-0.5.2.2.orig/hackage-security.cabal hackage-security-0.5.2.2/hackage-security.cabal ---- hackage-security-0.5.2.2.orig/hackage-security.cabal 2016-08-29 00:57:40.000000000 +0200 -+++ hackage-security-0.5.2.2/hackage-security.cabal 2017-12-03 14:48:08.028484227 +0100 -@@ -1,245 +1,245 @@ --name: hackage-security --version: 0.5.2.2 --synopsis: Hackage security library --description: The hackage security library provides both server and -- client utilities for securing the Hackage package server -- (<http://hackage.haskell.org/>). It is based on The Update -- Framework (<http://theupdateframework.com/>), a set of -- recommendations developed by security researchers at -- various universities in the US as well as developers on the -- Tor project (<https://www.torproject.org/>). -- . -- The current implementation supports only index signing, -- thereby enabling untrusted mirrors. It does not yet provide -- facilities for author package signing. -- . -- The library has two main entry points: -- "Hackage.Security.Client" is the main entry point for -- clients (the typical example being @cabal@), and -- "Hackage.Security.Server" is the main entry point for -- servers (the typical example being @hackage-server@). --license: BSD3 --license-file: LICENSE --author: Edsko de Vries --maintainer: edsko@well-typed.com --copyright: Copyright 2015-2016 Well-Typed LLP --category: Distribution --homepage: https://github.com/well-typed/hackage-security --bug-reports: https://github.com/well-typed/hackage-security/issues --build-type: Simple --cabal-version: >=1.10 -- --extra-source-files: -- ChangeLog.md -- --source-repository head -- type: git -- location: https://github.com/well-typed/hackage-security.git -- --flag base48 -- description: Are we using base 4.8 or later? -- manual: False -- --flag use-network-uri -- description: Are we using network-uri? -- manual: False -- --Flag old-directory -- description: Use directory < 1.2 and old-time -- manual: False -- default: False -- --library -- -- Most functionality is exported through the top-level entry points .Client -- -- and .Server; the other exported modules are intended for qualified imports. -- exposed-modules: Hackage.Security.Client -- Hackage.Security.Client.Formats -- Hackage.Security.Client.Repository -- Hackage.Security.Client.Repository.Cache -- Hackage.Security.Client.Repository.Local -- Hackage.Security.Client.Repository.Remote -- Hackage.Security.Client.Repository.HttpLib -- Hackage.Security.Client.Verify -- Hackage.Security.JSON -- Hackage.Security.Key.Env -- Hackage.Security.Server -- Hackage.Security.Trusted -- Hackage.Security.TUF.FileMap -- Hackage.Security.Util.Checked -- Hackage.Security.Util.IO -- Hackage.Security.Util.Lens -- Hackage.Security.Util.Path -- Hackage.Security.Util.Pretty -- Hackage.Security.Util.Some -- Text.JSON.Canonical -- other-modules: Hackage.Security.Key -- Hackage.Security.Trusted.TCB -- Hackage.Security.TUF -- Hackage.Security.TUF.Common -- Hackage.Security.TUF.FileInfo -- Hackage.Security.TUF.Header -- Hackage.Security.TUF.Layout.Cache -- Hackage.Security.TUF.Layout.Index -- Hackage.Security.TUF.Layout.Repo -- Hackage.Security.TUF.Mirrors -- Hackage.Security.TUF.Paths -- Hackage.Security.TUF.Patterns -- Hackage.Security.TUF.Root -- Hackage.Security.TUF.Signed -- Hackage.Security.TUF.Snapshot -- Hackage.Security.TUF.Targets -- Hackage.Security.TUF.Timestamp -- Hackage.Security.Util.Base64 -- Hackage.Security.Util.JSON -- Hackage.Security.Util.Stack -- Hackage.Security.Util.TypedEmbedded -- Prelude -- -- We support ghc 7.4 (bundled with Cabal 1.14) and up -- build-depends: base >= 4.5 && < 5, -- base16-bytestring >= 0.1.1 && < 0.2, -- base64-bytestring >= 1.0 && < 1.1, -- bytestring >= 0.9 && < 0.11, -- Cabal >= 1.14 && < 1.26, -- containers >= 0.4 && < 0.6, -- directory >= 1.1.0.2 && < 1.3, -- ed25519 >= 0.0 && < 0.1, -- filepath >= 1.2 && < 1.5, -- mtl >= 2.2 && < 2.3, -- parsec >= 3.1 && < 3.2, -- pretty >= 1.0 && < 1.2, -- cryptohash-sha256 >= 0.11 && < 0.12, -- -- 0.4.2 introduces TarIndex, 0.4.4 introduces more -- -- functionality, 0.5.0 changes type of serialise -- tar >= 0.5 && < 0.6, -- time >= 1.2 && < 1.7, -- transformers >= 0.4 && < 0.6, -- zlib >= 0.5 && < 0.7, -- -- whatever versions are bundled with ghc: -- template-haskell, -- ghc-prim -- if flag(old-directory) -- build-depends: directory < 1.2, old-time >= 1 && < 1.2 -- else -- build-depends: directory >= 1.2 -- hs-source-dirs: src -- default-language: Haskell2010 -- default-extensions: DefaultSignatures -- DeriveDataTypeable -- DeriveFunctor -- FlexibleContexts -- FlexibleInstances -- GADTs -- GeneralizedNewtypeDeriving -- KindSignatures -- MultiParamTypeClasses -- NamedFieldPuns -- NoMonomorphismRestriction -- RankNTypes -- RecordWildCards -- ScopedTypeVariables -- StandaloneDeriving -- TupleSections -- TypeFamilies -- TypeOperators -- ViewPatterns -- other-extensions: BangPatterns -- CPP -- OverlappingInstances -- PackageImports -- UndecidableInstances -- -- use the new stage1/cross-compile-friendly Quotes subset of TH for new GHCs -- if impl(ghc >= 8.0) -- -- place holder until Hackage allows to edit in the new extension token -- -- other-extensions: TemplateHaskellQuotes -- other-extensions: -- else -- other-extensions: TemplateHaskell -- -- ghc-options: -Wall -- -- if flag(base48) -- build-depends: base >= 4.8 -- else -- build-depends: old-locale >= 1.0 -- -- -- The URI type got split out off the network package after version 2.5, and -- -- moved to a separate network-uri package. Since we don't need the rest of -- -- network here, it would suffice to rely only on network-uri: -- -- -- -- > if flag(use-network-uri) -- -- > build-depends: network-uri >= 2.6 && < 2.7 -- -- > else -- -- > build-depends: network >= 2.5 && < 2.6 -- -- -- -- However, if we did the same in hackage-security-HTTP, Cabal would consider -- -- those two flag choices (hackage-security:use-network-uri and -- -- hackage-security-HTTP:use-network-uri) to be completely independent; but -- -- they aren't: if it links hackage-security against network-uri and -- -- hackage-security-HTTP against network, we will get type errors when -- -- hackage-security-HTTP tries to pass a URI to hackage-security. -- -- -- -- It might seem we can solve this problem by re-exporting the URI type in -- -- hackage-security and avoid the dependency in hackage-security-HTTP -- -- altogether. However, this merely shifts the problem: hackage-security-HTTP -- -- relies on the HTTP library which--surprise!--makes the same choice between -- -- depending on network or network-uri. Cabal will not notice that we cannot -- -- build hackage-security and hackage-security-HTTP against network-uri but -- -- HTTP against network. -- -- -- -- We solve the problem by explicitly relying on network-2.6 when choosing -- -- network-uri. This dependency is redundant, strictly speaking. However, it -- -- serves as a proxy for forcing flag choices: since all packages in a -- -- solution must be linked against the same version of network, having one -- -- version of network in one branch of the conditional and another version of -- -- network in the other branch forces the choice to be consistent throughout. -- -- (Note that the HTTP library does the same thing, though in this case the -- -- dependency in network is not redundant.) -- if flag(use-network-uri) -- build-depends: network-uri >= 2.6 && < 2.7, -- network >= 2.6 && < 2.7 -- else -- build-depends: network >= 2.5 && < 2.6 -- -- if impl(ghc >= 7.8) -- other-extensions: RoleAnnotations -- -- if impl(ghc >= 7.10) -- other-extensions: AllowAmbiguousTypes ---- StaticPointers ---- ^^^ Temporarily disabled because Hackage doesn't know yet about this ---- extension and will therefore reject this package. -- --test-suite TestSuite -- type: exitcode-stdio-1.0 -- main-is: TestSuite.hs -- other-modules: TestSuite.HttpMem -- TestSuite.InMemCache -- TestSuite.InMemRepo -- TestSuite.InMemRepository -- TestSuite.JSON -- TestSuite.PrivateKeys -- TestSuite.Util.StrictMVar -- build-depends: base, -- Cabal, -- containers, -- HUnit, -- bytestring, -- hackage-security, -- network-uri, -- tar, -- tasty, -- tasty-hunit, -- tasty-quickcheck, -- QuickCheck, -- temporary, -- time, -- zlib -- hs-source-dirs: tests -- default-language: Haskell2010 -- default-extensions: FlexibleContexts -- GADTs -- KindSignatures -- RankNTypes -- RecordWildCards -- ScopedTypeVariables -- ghc-options: -Wall -+name: hackage-security -+version: 0.5.2.2 -+x-revision: 4 -+-- xrevision:1 integrates -+-- https://github.com/well-typed/hackage-security/commit/e4bff90a82a588ff2d0beedfc50d5fdf75861d48 -+synopsis: Hackage security library -+description: The hackage security library provides both server and -+ client utilities for securing the Hackage package server -+ (<http://hackage.haskell.org/>). It is based on The Update -+ Framework (<http://theupdateframework.com/>), a set of -+ recommendations developed by security researchers at -+ various universities in the US as well as developers on the -+ Tor project (<https://www.torproject.org/>). -+ . -+ The current implementation supports only index signing, -+ thereby enabling untrusted mirrors. It does not yet provide -+ facilities for author package signing. -+ . -+ The library has two main entry points: -+ "Hackage.Security.Client" is the main entry point for -+ clients (the typical example being @cabal@), and -+ "Hackage.Security.Server" is the main entry point for -+ servers (the typical example being @hackage-server@). -+license: BSD3 -+license-file: LICENSE -+author: Edsko de Vries -+maintainer: edsko@well-typed.com -+copyright: Copyright 2015-2016 Well-Typed LLP -+category: Distribution -+homepage: https://github.com/well-typed/hackage-security -+bug-reports: https://github.com/well-typed/hackage-security/issues -+build-type: Simple -+cabal-version: >=1.10 -+ -+extra-source-files: -+ ChangeLog.md -+ -+source-repository head -+ type: git -+ location: https://github.com/well-typed/hackage-security.git -+ -+flag base48 -+ description: Are we using base 4.8 or later? -+ manual: False -+ -+flag use-network-uri -+ description: Are we using network-uri? -+ manual: False -+ -+Flag old-directory -+ description: Use directory < 1.2 and old-time -+ manual: False -+ default: False -+ -+ -+library -+ -- Most functionality is exported through the top-level entry points .Client -+ -- and .Server; the other exported modules are intended for qualified imports. -+ exposed-modules: Hackage.Security.Client -+ Hackage.Security.Client.Formats -+ Hackage.Security.Client.Repository -+ Hackage.Security.Client.Repository.Cache -+ Hackage.Security.Client.Repository.Local -+ Hackage.Security.Client.Repository.Remote -+ Hackage.Security.Client.Repository.HttpLib -+ Hackage.Security.Client.Verify -+ Hackage.Security.JSON -+ Hackage.Security.Key.Env -+ Hackage.Security.Server -+ Hackage.Security.Trusted -+ Hackage.Security.TUF.FileMap -+ Hackage.Security.Util.Checked -+ Hackage.Security.Util.IO -+ Hackage.Security.Util.Lens -+ Hackage.Security.Util.Path -+ Hackage.Security.Util.Pretty -+ Hackage.Security.Util.Some -+ Text.JSON.Canonical -+ other-modules: Hackage.Security.Key -+ Hackage.Security.Trusted.TCB -+ Hackage.Security.TUF -+ Hackage.Security.TUF.Common -+ Hackage.Security.TUF.FileInfo -+ Hackage.Security.TUF.Header -+ Hackage.Security.TUF.Layout.Cache -+ Hackage.Security.TUF.Layout.Index -+ Hackage.Security.TUF.Layout.Repo -+ Hackage.Security.TUF.Mirrors -+ Hackage.Security.TUF.Paths -+ Hackage.Security.TUF.Patterns -+ Hackage.Security.TUF.Root -+ Hackage.Security.TUF.Signed -+ Hackage.Security.TUF.Snapshot -+ Hackage.Security.TUF.Targets -+ Hackage.Security.TUF.Timestamp -+ Hackage.Security.Util.Base64 -+ Hackage.Security.Util.JSON -+ Hackage.Security.Util.Stack -+ Hackage.Security.Util.TypedEmbedded -+ Prelude -+ -- We support ghc 7.4 (bundled with Cabal 1.14) and up -+ build-depends: base >= 4.5 && < 5, -+ base16-bytestring >= 0.1.1 && < 0.2, -+ base64-bytestring >= 1.0 && < 1.1, -+ bytestring >= 0.9 && < 0.11, -+ Cabal >= 1.14 && < 2.2, -+ containers >= 0.4 && < 0.6, -+ directory >= 1.1.0.2 && < 1.4, -+ ed25519 >= 0.0 && < 0.1, -+ filepath >= 1.2 && < 1.5, -+ mtl >= 2.2 && < 2.3, -+ parsec >= 3.1 && < 3.2, -+ pretty >= 1.0 && < 1.2, -+ cryptohash-sha256 >= 0.11 && < 0.12, -+ -- 0.4.2 introduces TarIndex, 0.4.4 introduces more -+ -- functionality, 0.5.0 changes type of serialise -+ tar >= 0.5 && < 0.6, -+ time >= 1.2 && < 1.9, -+ transformers >= 0.4 && < 0.6, -+ zlib >= 0.5 && < 0.7, -+ -- whatever versions are bundled with ghc: -+ template-haskell, -+ ghc-prim -+ if flag(old-directory) -+ build-depends: directory < 1.2, old-time >= 1 && < 1.2 -+ else -+ build-depends: directory >= 1.2 -+ hs-source-dirs: src -+ default-language: Haskell2010 -+ default-extensions: DefaultSignatures -+ DeriveDataTypeable -+ DeriveFunctor -+ FlexibleContexts -+ FlexibleInstances -+ GADTs -+ GeneralizedNewtypeDeriving -+ KindSignatures -+ MultiParamTypeClasses -+ NamedFieldPuns -+ NoMonomorphismRestriction -+ RankNTypes -+ RecordWildCards -+ ScopedTypeVariables -+ StandaloneDeriving -+ TupleSections -+ TypeFamilies -+ TypeOperators -+ ViewPatterns -+ other-extensions: BangPatterns -+ CPP -+ OverlappingInstances -+ PackageImports -+ UndecidableInstances -+ -- use the new stage1/cross-compile-friendly Quotes subset of TH for new GHCs -+ if impl(ghc >= 8.0) -+ other-extensions: TemplateHaskellQuotes -+ else -+ other-extensions: TemplateHaskell -+ -+ ghc-options: -Wall -+ -+ if flag(base48) -+ build-depends: base >= 4.8 -+ else -+ build-depends: base < 4.8, old-locale >= 1.0 -+ -+ -- The URI type got split out off the network package after version 2.5, and -+ -- moved to a separate network-uri package. Since we don't need the rest of -+ -- network here, it would suffice to rely only on network-uri: -+ -- -+ -- > if flag(use-network-uri) -+ -- > build-depends: network-uri >= 2.6 && < 2.7 -+ -- > else -+ -- > build-depends: network >= 2.5 && < 2.6 -+ -- -+ -- However, if we did the same in hackage-security-HTTP, Cabal would consider -+ -- those two flag choices (hackage-security:use-network-uri and -+ -- hackage-security-HTTP:use-network-uri) to be completely independent; but -+ -- they aren't: if it links hackage-security against network-uri and -+ -- hackage-security-HTTP against network, we will get type errors when -+ -- hackage-security-HTTP tries to pass a URI to hackage-security. -+ -- -+ -- It might seem we can solve this problem by re-exporting the URI type in -+ -- hackage-security and avoid the dependency in hackage-security-HTTP -+ -- altogether. However, this merely shifts the problem: hackage-security-HTTP -+ -- relies on the HTTP library which--surprise!--makes the same choice between -+ -- depending on network or network-uri. Cabal will not notice that we cannot -+ -- build hackage-security and hackage-security-HTTP against network-uri but -+ -- HTTP against network. -+ -- -+ -- We solve the problem by explicitly relying on network-2.6 when choosing -+ -- network-uri. This dependency is redundant, strictly speaking. However, it -+ -- serves as a proxy for forcing flag choices: since all packages in a -+ -- solution must be linked against the same version of network, having one -+ -- version of network in one branch of the conditional and another version of -+ -- network in the other branch forces the choice to be consistent throughout. -+ -- (Note that the HTTP library does the same thing, though in this case the -+ -- dependency in network is not redundant.) -+ if flag(use-network-uri) -+ build-depends: network-uri >= 2.6 && < 2.7, -+ network >= 2.6 && < 2.7 -+ else -+ build-depends: network >= 2.5 && < 2.6 -+ -+ if impl(ghc >= 7.8) -+ other-extensions: RoleAnnotations -+ -+ if impl(ghc >= 7.10) -+ other-extensions: AllowAmbiguousTypes -+ StaticPointers -+ -+test-suite TestSuite -+ type: exitcode-stdio-1.0 -+ main-is: TestSuite.hs -+ other-modules: TestSuite.HttpMem -+ TestSuite.InMemCache -+ TestSuite.InMemRepo -+ TestSuite.InMemRepository -+ TestSuite.JSON -+ TestSuite.PrivateKeys -+ TestSuite.Util.StrictMVar -+ build-depends: base, -+ Cabal < 1.25, -+ containers, -+ HUnit, -+ bytestring, -+ hackage-security, -+ network-uri, -+ tar, -+ tasty, -+ tasty-hunit, -+ tasty-quickcheck, -+ QuickCheck, -+ temporary, -+ time, -+ zlib -+ hs-source-dirs: tests -+ default-language: Haskell2010 -+ default-extensions: FlexibleContexts -+ GADTs -+ KindSignatures -+ RankNTypes -+ RecordWildCards -+ ScopedTypeVariables -+ ghc-options: -Wall -diff -ru hackage-security-0.5.2.2.orig/src/Text/JSON/Canonical.hs hackage-security-0.5.2.2/src/Text/JSON/Canonical.hs ---- hackage-security-0.5.2.2.orig/src/Text/JSON/Canonical.hs 2016-08-29 00:57:40.000000000 +0200 -+++ hackage-security-0.5.2.2/src/Text/JSON/Canonical.hs 2017-12-03 15:03:38.522825262 +0100 -@@ -321,8 +321,8 @@ - jstring = doubleQuotes . hcat . map jchar - - jchar :: Char -> Doc --jchar '"' = Doc.char '\\' <> Doc.char '"' --jchar '\\' = Doc.char '\\' <> Doc.char '\\' -+jchar '"' = Doc.char '\\' Doc.<> Doc.char '"' -+jchar '\\' = Doc.char '\\' Doc.<> Doc.char '\\' - jchar c = Doc.char c - - jarray :: [JSValue] -> Doc -@@ -331,7 +331,7 @@ - - jobject :: [(String, JSValue)] -> Doc - jobject = sep . punctuate' lbrace comma rbrace -- . map (\(k,v) -> sep [jstring k <> colon, nest 2 (jvalue v)]) -+ . map (\(k,v) -> sep [jstring k Doc.<> colon, nest 2 (jvalue v)]) - - - -- | Punctuate in this style: -@@ -345,7 +345,7 @@ - -- > ] - -- - punctuate' :: Doc -> Doc -> Doc -> [Doc] -> [Doc] --punctuate' l _ r [] = [l <> r] -+punctuate' l _ r [] = [l Doc.<> r] - punctuate' l _ r [x] = [l <+> x <+> r] - punctuate' l p r (x:xs) = l <+> x : go xs - where diff --git a/patches/happy-1.19.8.patch b/patches/happy-1.19.8.patch deleted file mode 100644 index d4fb6e417609430518d78587244dc9d9d8ddd0d5..0000000000000000000000000000000000000000 --- a/patches/happy-1.19.8.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff --git a/src/PrettyGrammar.hs b/src/PrettyGrammar.hs -index 6bfddac..811bd8d 100644 ---- a/src/PrettyGrammar.hs -+++ b/src/PrettyGrammar.hs -@@ -1,6 +1,7 @@ - module PrettyGrammar where - - import AbsSyn -+import Prelude hiding ((<>)) - - render :: Doc -> String - render = maybe "" ($ "") diff --git a/patches/hashtables-1.2.2.1.patch b/patches/hashtables-1.2.2.1.patch deleted file mode 100644 index 69c2d94c2f1b108c5771ddac8a3268f33930f5a6..0000000000000000000000000000000000000000 --- a/patches/hashtables-1.2.2.1.patch +++ /dev/null @@ -1,42 +0,0 @@ -diff --git a/hashtables.cabal b/hashtables.cabal -index 42a4da7..f7e22e0 100644 ---- a/hashtables.cabal -+++ b/hashtables.cabal -@@ -174,6 +174,7 @@ Library - - Build-depends: base >= 4.7 && <5, - hashable >= 1.1 && <1.2 || >= 1.2.1 && <1.3, -+ semigroups >= 0.18 && <0.19, - primitive, - vector >= 0.7 && <0.13 - -diff --git a/src/Data/HashTable/ST/Basic.hs b/src/Data/HashTable/ST/Basic.hs -index 7b3983c..8fba2d1 100644 ---- a/src/Data/HashTable/ST/Basic.hs -+++ b/src/Data/HashTable/ST/Basic.hs -@@ -103,6 +103,7 @@ import Data.Hashable (Hashable) - import qualified Data.Hashable as H - import Data.Maybe - import Data.Monoid -+import Data.Semigroup - import qualified Data.Primitive.ByteArray as A - import Data.STRef - import GHC.Exts -@@ -488,12 +489,14 @@ newtype Slot = Slot { _slot :: Int } deriving (Show) - - - ------------------------------------------------------------------------------ --instance Monoid Slot where -- mempty = Slot maxBound -- (Slot x1) `mappend` (Slot x2) = -+instance Semigroup Slot where -+ Slot x1 <> Slot x2 = - let !m = mask x1 maxBound - in Slot $! (complement m .&. x1) .|. (m .&. x2) - -+instance Monoid Slot where -+ mempty = Slot maxBound -+ mappend = (<>) - - ------------------------------------------------------------------------------ - -- findSafeSlots return type diff --git a/patches/haskell-src-exts-1.20.1.patch b/patches/haskell-src-exts-1.20.1.patch deleted file mode 100644 index 740e6e932b3e2335d7050608d20608e5e617d89a..0000000000000000000000000000000000000000 --- a/patches/haskell-src-exts-1.20.1.patch +++ /dev/null @@ -1,91 +0,0 @@ -commit f1ab604faf30672af3581ed1370c8d88d7ebf28f -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Dec 28 12:02:29 2017 -0500 - - Adapt to the Semigroup–Monoid Proposal - -diff --git a/src/Language/Haskell/Exts/InternalParser.ly b/src/Language/Haskell/Exts/InternalParse -index ee20f64..8a8ea96 100644 ---- a/src/Language/Haskell/Exts/InternalParser.ly -+++ b/src/Language/Haskell/Exts/InternalParser.ly -@@ -1,4 +1,5 @@ - > { -+> {-# LANGUAGE CPP #-} - > {-# OPTIONS_HADDOCK hide #-} - > ----------------------------------------------------------------------------- - > -- | -@@ -40,6 +41,9 @@ - > import Control.Monad ( liftM, (<=<), when ) - > import Control.Applicative ( (<$>) ) - > import Data.Maybe -+> #if MIN_VERSION_base(4,11,0) -+> import Prelude hiding ((<>)) -+> #endif - import Debug.Trace (trace) - - > } -diff --git a/src/Language/Haskell/Exts/ParseMonad.hs b/src/Language/Haskell/Exts/ParseMonad.hs -index bc77eb5..209e76b 100644 ---- a/src/Language/Haskell/Exts/ParseMonad.hs -+++ b/src/Language/Haskell/Exts/ParseMonad.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# OPTIONS_HADDOCK hide #-} - ----------------------------------------------------------------------------- - -- | -@@ -45,7 +46,10 @@ import Language.Haskell.Exts.Extension -- (Extension, impliesExts, haskell2010) - import Data.List (intercalate) - import Control.Applicative - import Control.Monad (when, liftM, ap) --import Data.Monoid -+import Data.Monoid hiding ((<>)) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - -- To avoid import warnings for Control.Applicative and Data.Monoid - import Prelude - -@@ -98,12 +102,24 @@ instance Monad ParseResult where - ParseOk x >>= f = f x - ParseFailed loc msg >>= _ = ParseFailed loc msg - --instance Monoid m => Monoid (ParseResult m) where -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup m => Semigroup (ParseResult m) where -+ ParseOk x <> ParseOk y = ParseOk $ x <> y -+ ParseOk _ <> err = err -+ err <> _ = err -- left-biased -+#endif -+ -+instance ( Monoid m -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+ , Semigroup m -+#endif -+ ) => Monoid (ParseResult m) where - mempty = ParseOk mempty -+#if !(MIN_VERSION_base(4,11,0)) - ParseOk x `mappend` ParseOk y = ParseOk $ x `mappend` y - ParseOk _ `mappend` err = err - err `mappend` _ = err -- left-biased -- -+#endif - - -- internal version - data ParseStatus a = Ok ParseState a | Failed SrcLoc String -diff --git a/src/Language/Haskell/Exts/Pretty.hs b/src/Language/Haskell/Exts/Pretty.hs -index c03e438..adced3f 100644 ---- a/src/Language/Haskell/Exts/Pretty.hs -+++ b/src/Language/Haskell/Exts/Pretty.hs -@@ -31,7 +31,11 @@ import qualified Language.Haskell.Exts.ParseSyntax as P - - import Language.Haskell.Exts.SrcLoc hiding (loc) - --import Prelude hiding (exp) -+import Prelude hiding ( exp -+#if MIN_VERSION_base(4,11,0) -+ , (<>) -+#endif -+ ) - import qualified Text.PrettyPrint as P - import Data.List (intersperse) - import Data.Maybe (isJust , fromMaybe) diff --git a/patches/haskell-src-exts-util-0.2.1.2.patch b/patches/haskell-src-exts-util-0.2.1.2.patch deleted file mode 100644 index 24d7e74ae14aee85c539b2c6efa0604f150c2df7..0000000000000000000000000000000000000000 --- a/patches/haskell-src-exts-util-0.2.1.2.patch +++ /dev/null @@ -1,42 +0,0 @@ -diff -ru haskell-src-exts-util-0.2.1.2.orig/haskell-src-exts-util.cabal haskell-src-exts-util-0.2.1.2/haskell-src-exts-util.cabal ---- haskell-src-exts-util-0.2.1.2.orig/haskell-src-exts-util.cabal 2018-01-06 17:14:37.088772378 -0500 -+++ haskell-src-exts-util-0.2.1.2/haskell-src-exts-util.cabal 2018-01-06 17:17:23.304776564 -0500 -@@ -27,6 +27,7 @@ - , containers - , data-default - , haskell-src-exts -+ , semigroups - , transformers - , uniplate - exposed-modules: -diff -ru haskell-src-exts-util-0.2.1.2.orig/src/Language/Haskell/Exts/FreeVars.hs haskell-src-exts-util-0.2.1.2/src/Language/Haskell/Exts/FreeVars.hs ---- haskell-src-exts-util-0.2.1.2.orig/src/Language/Haskell/Exts/FreeVars.hs 2017-08-25 15:48:57.000000000 -0400 -+++ haskell-src-exts-util-0.2.1.2/src/Language/Haskell/Exts/FreeVars.hs 2018-01-06 17:18:25.852778139 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE FlexibleContexts #-} - {-# LANGUAGE FlexibleInstances #-} - {-# LANGUAGE ScopedTypeVariables #-} -@@ -16,6 +17,7 @@ - import Data.Data - import Data.Generics.Uniplate.Data - import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.Set (Set) - import qualified Data.Set as Set - import Language.Haskell.Exts -@@ -28,9 +30,14 @@ - - data Vars = Vars {bound :: Set (Name ()), free :: Set (Name ())} - -+instance Semigroup Vars where -+ Vars x1 x2 <> Vars y1 y2 = Vars (x1 ^+ y1) (x2 ^+ y2) -+ - instance Monoid Vars where - mempty = Vars Set.empty Set.empty -+#if !(MIN_VERSION_base(4,11,0)) - mappend (Vars x1 x2) (Vars y1 y2) = Vars (x1 ^+ y1) (x2 ^+ y2) -+#endif - mconcat fvs = Vars (Set.unions $ map bound fvs) (Set.unions $ map free fvs) - - class AllVars a where diff --git a/patches/heaps-0.3.5.patch b/patches/heaps-0.3.5.patch deleted file mode 100644 index 1e34533869d1bdb0eae560d5752c27a027132875..0000000000000000000000000000000000000000 --- a/patches/heaps-0.3.5.patch +++ /dev/null @@ -1,144 +0,0 @@ -diff -ru heaps-0.3.5.orig/heaps.cabal heaps-0.3.5/heaps.cabal ---- heaps-0.3.5.orig/heaps.cabal 2017-07-29 02:34:39.000000000 +0200 -+++ heaps-0.3.5/heaps.cabal 2017-09-17 11:03:50.473204188 +0200 -@@ -1,53 +1,54 @@ --name: heaps --version: 0.3.5 --license: BSD3 --license-file: LICENSE --author: Edward A. Kmett --maintainer: Edward A. Kmett <ekmett@gmail.com> --stability: experimental --homepage: http://github.com/ekmett/heaps/ --bug-reports: http://github.com/ekmett/heaps/issues --category: Data Structures --synopsis: Asymptotically optimal Brodal/Okasaki heaps. --description: Asymptotically optimal Brodal\/Okasaki bootstrapped skew-binomial heaps from the paper <http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.48.973 "Optimal Purely Functional Priority Queues">, extended with a 'Foldable' interface. --copyright: (c) 2010-2015 Edward A. Kmett --tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.3, GHC == 8.0.2, GHC == 8.2.1 --build-type: Custom --cabal-version: >=1.8 --extra-source-files: -- HLint.hs -- Warning.hs -- .gitignore -- .travis.yml -- CHANGELOG.markdown -- README.markdown -- --custom-setup -- setup-depends: -- base >= 4.3 && <5, -- Cabal >= 1.10, -- cabal-doctest >= 1 && <1.1 -- --source-repository head -- type: git -- location: git://github.com/ekmett/heaps.git -- --library -- exposed-modules: Data.Heap -- build-depends: -- base >= 4 && < 6 -- hs-source-dirs: src -- ghc-options: -O2 -- ---- Verify the results of the examples --test-suite doctests -- type: exitcode-stdio-1.0 -- main-is: doctests.hs -- build-depends: -- base, -- directory >= 1.0 && < 1.4, -- doctest >= 0.9 && < 0.13, -- filepath, -- heaps -- ghc-options: -Wall -- hs-source-dirs: tests -+name: heaps -+version: 0.3.5 -+x-revision: 1 -+license: BSD3 -+license-file: LICENSE -+author: Edward A. Kmett -+maintainer: Edward A. Kmett <ekmett@gmail.com> -+stability: experimental -+homepage: http://github.com/ekmett/heaps/ -+bug-reports: http://github.com/ekmett/heaps/issues -+category: Data Structures -+synopsis: Asymptotically optimal Brodal/Okasaki heaps. -+description: Asymptotically optimal Brodal\/Okasaki bootstrapped skew-binomial heaps from the paper <http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.48.973 "Optimal Purely Functional Priority Queues">, extended with a 'Foldable' interface. -+copyright: (c) 2010-2015 Edward A. Kmett -+tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.3, GHC == 8.0.2, GHC == 8.2.1 -+build-type: Custom -+cabal-version: >=1.8 -+extra-source-files: -+ HLint.hs -+ Warning.hs -+ .gitignore -+ .travis.yml -+ CHANGELOG.markdown -+ README.markdown -+ -+custom-setup -+ setup-depends: -+ base >= 4.3 && <5, -+ Cabal >= 1.10, -+ cabal-doctest >= 1 && <1.1 -+ -+source-repository head -+ type: git -+ location: git://github.com/ekmett/heaps.git -+ -+library -+ exposed-modules: Data.Heap -+ build-depends: -+ base >= 4 && < 6 -+ hs-source-dirs: src -+ ghc-options: -O2 -+ -+-- Verify the results of the examples -+test-suite doctests -+ type: exitcode-stdio-1.0 -+ main-is: doctests.hs -+ build-depends: -+ base, -+ directory >= 1.0 && < 1.4, -+ doctest >= 0.9 && < 0.14, -+ filepath, -+ heaps -+ ghc-options: -Wall -+ hs-source-dirs: tests -diff -ru heaps-0.3.5.orig/src/Data/Heap.hs heaps-0.3.5/src/Data/Heap.hs ---- heaps-0.3.5.orig/src/Data/Heap.hs 2017-07-29 02:34:39.000000000 +0200 -+++ heaps-0.3.5/src/Data/Heap.hs 2017-09-17 11:05:14.560727487 +0200 -@@ -94,6 +94,9 @@ - import qualified Data.List as L - import Control.Applicative (Applicative(pure)) - import Control.Monad (liftM) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup (Semigroup(..)) -+#endif - import Data.Monoid (Monoid(mappend, mempty)) - import Data.Foldable hiding (minimum, concatMap) - import Data.Function (on) -@@ -377,11 +380,19 @@ - sort = toList . fromList - {-# INLINE sort #-} - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup (Heap a) where -+ (<>) = union -+ {-# INLINE (<>) #-} -+#endif -+ - instance Monoid (Heap a) where - mempty = empty - {-# INLINE mempty #-} -+#if !(MIN_VERSION_base(4,11,0)) - mappend = union - {-# INLINE mappend #-} -+#endif - - -- | /O(n)/. Returns the elements in the heap in some arbitrary, very likely unsorted, order. - -- diff --git a/patches/hlint-2.0.12.patch b/patches/hlint-2.0.12.patch deleted file mode 100644 index fe10349e77582de08034152a68551e0f4c9470a1..0000000000000000000000000000000000000000 --- a/patches/hlint-2.0.12.patch +++ /dev/null @@ -1,171 +0,0 @@ -diff -ru hlint-2.0.12.orig/src/Config/Yaml.hs hlint-2.0.12/src/Config/Yaml.hs ---- hlint-2.0.12.orig/src/Config/Yaml.hs 2017-12-12 09:12:49.000000000 -0500 -+++ hlint-2.0.12/src/Config/Yaml.hs 2018-01-12 12:32:39.909401432 -0500 -@@ -20,7 +20,7 @@ - import qualified Data.HashMap.Strict as Map - import HSE.All hiding (Rule, String) - import Data.Functor --import Data.Monoid -+import Data.Semigroup - import Util - import Prelude - -@@ -40,7 +40,7 @@ - --------------------------------------------------------------------- - -- YAML DATA TYPE - --newtype ConfigYaml = ConfigYaml [ConfigItem] deriving (Monoid,Show) -+newtype ConfigYaml = ConfigYaml [ConfigItem] deriving (Semigroup,Monoid,Show) - - data ConfigItem - = ConfigPackage Package -diff -ru hlint-2.0.12.orig/src/Hint/Extensions.hs hlint-2.0.12/src/Hint/Extensions.hs ---- hlint-2.0.12.orig/src/Hint/Extensions.hs 2017-12-12 09:12:50.000000000 -0500 -+++ hlint-2.0.12/src/Hint/Extensions.hs 2018-01-12 12:32:39.909401432 -0500 -@@ -123,7 +123,7 @@ - import Data.Ratio - import Data.Data - import Refact.Types --import Data.Monoid -+import Data.Semigroup - import Prelude - - -@@ -244,10 +244,12 @@ - ,derivesData :: [String] - ,derivesStandalone :: [String] - } -+instance Semigroup Derives where -+ Derives x1 x2 x3 <> Derives y1 y2 y3 = -+ Derives (x1++y1) (x2++y2) (x3++y3) - instance Monoid Derives where - mempty = Derives [] [] [] -- mappend (Derives x1 x2 x3) (Derives y1 y2 y3) = -- Derives (x1++y1) (x2++y2) (x3++y3) -+ mappend = (<>) - - -- | What is derived on newtype, and on data type - -- 'deriving' declarations may be on either, so we approximate as both newtype and data -diff -ru hlint-2.0.12.orig/src/Hint/Restrict.hs hlint-2.0.12/src/Hint/Restrict.hs ---- hlint-2.0.12.orig/src/Hint/Restrict.hs 2017-12-12 09:12:50.000000000 -0500 -+++ hlint-2.0.12/src/Hint/Restrict.hs 2018-01-12 12:32:39.909401432 -0500 -@@ -17,7 +17,7 @@ - import Hint.Type - import Data.List - import Data.Maybe --import Data.Monoid -+import Data.Semigroup - import Control.Applicative - import Prelude - -@@ -39,9 +39,11 @@ - {riAs :: [String] - ,riWithin :: [(String, String)] - } -+instance Semigroup RestrictItem where -+ RestrictItem x1 x2 <> RestrictItem y1 y2 = RestrictItem (x1<>y1) (x2<>y2) - instance Monoid RestrictItem where - mempty = RestrictItem [] [] -- mappend (RestrictItem x1 x2) (RestrictItem y1 y2) = RestrictItem (x1<>y1) (x2<>y2) -+ mappend = (<>) - - restrictions :: [Setting] -> Map.Map RestrictType (Bool, Map.Map String RestrictItem) - restrictions settings = Map.map f $ Map.fromListWith (++) [(restrictType x, [x]) | SettingRestrict x <- settings] -diff -ru hlint-2.0.12.orig/src/Hint/Type.hs hlint-2.0.12/src/Hint/Type.hs ---- hlint-2.0.12.orig/src/Hint/Type.hs 2017-12-12 09:12:50.000000000 -0500 -+++ hlint-2.0.12/src/Hint/Type.hs 2018-01-12 12:32:39.909401432 -0500 -@@ -4,7 +4,7 @@ - module Export - ) where - --import Data.Monoid -+import Data.Semigroup - import Config.Type - import HSE.All as Export - import Idea as Export -@@ -26,10 +26,13 @@ - ,hintComment :: [Setting] -> Comment -> [Idea] -- ^ Given a comment generate some 'Idea's. - } - -+instance Semigroup Hint where -+ Hint x1 x2 x3 x4 <> Hint y1 y2 y3 y4 = Hint -+ (\a b -> x1 a b ++ y1 a b) -+ (\a b c -> x2 a b c ++ y2 a b c) -+ (\a b c d -> x3 a b c d ++ y3 a b c d) -+ (\a b -> x4 a b ++ y4 a b) -+ - instance Monoid Hint where - mempty = Hint (\_ _ -> []) (\_ _ _ -> []) (\_ _ _ _ -> []) (\_ _ -> []) -- mappend (Hint x1 x2 x3 x4) (Hint y1 y2 y3 y4) = Hint -- (\a b -> x1 a b ++ y1 a b) -- (\a b c -> x2 a b c ++ y2 a b c) -- (\a b c d -> x3 a b c d ++ y3 a b c d) -- (\a b -> x4 a b ++ y4 a b) -+ mappend = (<>) -diff -ru hlint-2.0.12.orig/src/HSE/Scope.hs hlint-2.0.12/src/HSE/Scope.hs ---- hlint-2.0.12.orig/src/HSE/Scope.hs 2017-12-12 09:12:49.000000000 -0500 -+++ hlint-2.0.12/src/HSE/Scope.hs 2018-01-12 12:34:00.761403468 -0500 -@@ -1,11 +1,11 @@ --{-# LANGUAGE ViewPatterns #-} -+{-# LANGUAGE ViewPatterns, GeneralizedNewtypeDeriving #-} - - module HSE.Scope( - Scope, scopeCreate, scopeImports, - scopeMatch, scopeMove - ) where - --import Data.Monoid -+import Data.Semigroup - import HSE.Type - import HSE.Util - import Data.List -@@ -34,11 +34,7 @@ - -- Note that the 'mempty' 'Scope' is not equivalent to 'scopeCreate' on an empty module, - -- due to the implicit import of 'Prelude'. - newtype Scope = Scope [ImportDecl S] -- deriving Show -- --instance Monoid Scope where -- mempty = Scope [] -- mappend (Scope xs) (Scope ys) = Scope $ xs ++ ys -+ deriving (Show, Monoid, Semigroup) - - -- | Create a 'Scope' value from a module, based on the modules imports. - scopeCreate :: Module SrcSpanInfo -> Scope -diff -ru hlint-2.0.12.orig/src/HSE/Unify.hs hlint-2.0.12/src/HSE/Unify.hs ---- hlint-2.0.12.orig/src/HSE/Unify.hs 2017-12-12 09:12:49.000000000 -0500 -+++ hlint-2.0.12/src/HSE/Unify.hs 2018-01-12 12:32:39.909401432 -0500 -@@ -1,4 +1,5 @@ - {-# LANGUAGE PatternGuards, ViewPatterns, FlexibleContexts, ScopedTypeVariables #-} -+{-# LANGUAGE GeneralizedNewtypeDeriving #-} - - module HSE.Unify( - Subst, fromSubst, -@@ -10,7 +11,7 @@ - import Data.List.Extra - import Data.Maybe - import Data.Data --import Data.Monoid -+import Data.Semigroup - import Config.Type - import Hint.Type - import Control.Monad -@@ -25,6 +26,7 @@ - -- | A list of substitutions. A key may be duplicated, you need to call 'check' - -- to ensure the substitution is valid. - newtype Subst a = Subst [(String, a)] -+ deriving (Semigroup, Monoid) - - -- | Unpack the substitution - fromSubst :: Subst a -> [(String, a)] -@@ -36,10 +38,6 @@ - instance Pretty a => Show (Subst a) where - show (Subst xs) = unlines [a ++ " = " ++ prettyPrint b | (a,b) <- xs] - --instance Monoid (Subst a) where -- mempty = Subst [] -- mappend (Subst xs) (Subst ys) = Subst $ xs ++ ys -- - - -- check the unification is valid and simplify it - validSubst :: (a -> a -> Bool) -> Subst a -> Maybe (Subst a) diff --git a/patches/hourglass-0.2.10.patch b/patches/hourglass-0.2.10.patch deleted file mode 100644 index d4c8ab2f3e2a7b34238ad1ea32959290dcaa7aaf..0000000000000000000000000000000000000000 --- a/patches/hourglass-0.2.10.patch +++ /dev/null @@ -1,45 +0,0 @@ -diff -ru hourglass-0.2.10.orig/Data/Hourglass/Diff.hs hourglass-0.2.10/Data/Hourglass/Diff.hs ---- hourglass-0.2.10.orig/Data/Hourglass/Diff.hs 2016-02-27 12:23:51.000000000 +0100 -+++ hourglass-0.2.10/Data/Hourglass/Diff.hs 2017-09-15 12:06:55.482606732 +0200 -@@ -20,6 +20,7 @@ - - import Data.Data - import Data.Monoid -+import Data.Semigroup - import Data.Hourglass.Types - import Data.Hourglass.Calendar - import Control.DeepSeq -@@ -38,10 +39,13 @@ - - instance NFData Period where - rnf (Period y m d) = y `seq` m `seq` d `seq` () -+ -+instance Semigroup Period where -+ (Period y1 m1 d1) <> (Period y2 m2 d2) = Period (y1+y2) (m1+m2) (d1+d2) -+ - instance Monoid Period where - mempty = Period 0 0 0 -- mappend (Period y1 m1 d1) (Period y2 m2 d2) = -- Period (y1+y2) (m1+m2) (d1+d2) -+ mappend = (<>) - - -- | An amount of time in terms of constant value like hours (3600 seconds), - -- minutes (60 seconds), seconds and nanoseconds. -@@ -54,10 +58,14 @@ - - instance NFData Duration where - rnf (Duration h m s ns) = h `seq` m `seq` s `seq` ns `seq` () -+ -+instance Semigroup Duration where -+ (Duration h1 m1 s1 ns1) <> (Duration h2 m2 s2 ns2) = Duration (h1+h2) (m1+m2) (s1+s2) (ns1+ns2) -+ - instance Monoid Duration where - mempty = Duration 0 0 0 0 -- mappend (Duration h1 m1 s1 ns1) (Duration h2 m2 s2 ns2) = -- Duration (h1+h2) (m1+m2) (s1+s2) (ns1+ns2) -+ mappend = (<>) -+ - instance TimeInterval Duration where - fromSeconds s = (durationNormalize (Duration 0 0 s 0), 0) - toSeconds d = fst $ durationFlatten d -Only in hourglass-0.2.10/Data/Hourglass: Diff.hs~ diff --git a/patches/hslogger-1.2.10.patch b/patches/hslogger-1.2.10.patch deleted file mode 100644 index d3ca504537f2531d2c6a899d7cdbabd054195245..0000000000000000000000000000000000000000 --- a/patches/hslogger-1.2.10.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -ru hslogger-1.2.10.orig/src/System/Log/Logger.hs hslogger-1.2.10/src/System/Log/Logger.hs ---- hslogger-1.2.10.orig/src/System/Log/Logger.hs 2016-05-29 09:42:33.000000000 -0400 -+++ hslogger-1.2.10/src/System/Log/Logger.hs 2018-07-04 21:47:31.436345560 -0400 -@@ -476,7 +476,7 @@ - removeAllHandlers :: IO () - removeAllHandlers = - modifyMVar_ logTree $ \lt -> do -- let allHandlers = Map.fold (\l r -> concat [r, handlers l]) [] lt -+ let allHandlers = Map.foldr (\l r -> concat [r, handlers l]) [] lt - mapM_ (\(HandlerT h) -> close h) allHandlers - return $ Map.map (\l -> l {handlers = []}) lt - diff --git a/patches/hspec-core-2.4.4.patch b/patches/hspec-core-2.4.4.patch deleted file mode 100644 index 7e8179387dd44994ec2c2fdaae10fb5f08cad5e7..0000000000000000000000000000000000000000 --- a/patches/hspec-core-2.4.4.patch +++ /dev/null @@ -1,37 +0,0 @@ -diff -ru hspec-core-2.4.4.orig/src/Test/Hspec/Core/Compat.hs hspec-core-2.4.4/src/Test/Hspec/Core/Compat.hs ---- hspec-core-2.4.4.orig/src/Test/Hspec/Core/Compat.hs 2017-06-16 11:08:23.000000000 +0200 -+++ hspec-core-2.4.4/src/Test/Hspec/Core/Compat.hs 2017-09-17 12:30:59.440828450 +0200 -@@ -12,6 +12,7 @@ - , module Data.Foldable - , module Data.Traversable - , module Data.Monoid -+, module Data.Semigroup - - #if !MIN_VERSION_base(4,6,0) - , modifyIORef' -@@ -21,7 +22,8 @@ - import Control.Applicative - import Data.Foldable - import Data.Traversable --import Data.Monoid -+import Data.Monoid hiding ((<>)) -+import Data.Semigroup (Semigroup(..)) - - import Prelude hiding ( - all -Only in hspec-core-2.4.4/src/Test/Hspec/Core: Compat.hs~ -diff -ru hspec-core-2.4.4.orig/src/Test/Hspec/Core/Runner.hs hspec-core-2.4.4/src/Test/Hspec/Core/Runner.hs ---- hspec-core-2.4.4.orig/src/Test/Hspec/Core/Runner.hs 2017-06-16 11:08:23.000000000 +0200 -+++ hspec-core-2.4.4/src/Test/Hspec/Core/Runner.hs 2017-09-17 12:31:26.856678058 +0200 -@@ -226,6 +226,9 @@ - , summaryFailures :: Int - } deriving (Eq, Show) - -+instance Semigroup Summary where -+ (Summary x1 x2) <> (Summary y1 y2) = Summary (x1 + y1) (x2 + y2) -+ - instance Monoid Summary where - mempty = Summary 0 0 -- (Summary x1 x2) `mappend` (Summary y1 y2) = Summary (x1 + y1) (x2 + y2) -+ mappend = (<>) -Only in hspec-core-2.4.4/src/Test/Hspec/Core: Runner.hs~ diff --git a/patches/hspec-meta-2.4.4.patch b/patches/hspec-meta-2.4.4.patch deleted file mode 100644 index 2b9beb48fd672e0bc96ea26b17abaede962699fc..0000000000000000000000000000000000000000 --- a/patches/hspec-meta-2.4.4.patch +++ /dev/null @@ -1,14 +0,0 @@ -diff --git a/hspec-core/src/Test/Hspec/Core/Runner.hs b/hspec-core/src/Test/Hspec/Core/Runner.hs -index dfc2c6e..e484681 100644 ---- a/hspec-core/src/Test/Hspec/Core/Runner.hs -+++ b/hspec-core/src/Test/Hspec/Core/Runner.hs -@@ -226,6 +226,9 @@ data Summary = Summary { - , summaryFailures :: Int - } deriving (Eq, Show) - -+instance Semigroup Summary where -+ (<>) = mappend -+ - instance Monoid Summary where - mempty = Summary 0 0 - (Summary x1 x2) `mappend` (Summary y1 y2) = Summary (x1 + y1) (x2 + y2) diff --git a/patches/http-api-data-0.3.7.1.patch b/patches/http-api-data-0.3.7.1.patch deleted file mode 100644 index 7396dc13cd6646cc3b2c9e5e5d7cf04cb0210ffb..0000000000000000000000000000000000000000 --- a/patches/http-api-data-0.3.7.1.patch +++ /dev/null @@ -1,24 +0,0 @@ -diff -ru http-api-data-0.3.7.1.orig/src/Web/Internal/FormUrlEncoded.hs http-api-data-0.3.7.1/src/Web/Internal/FormUrlEncoded.hs ---- http-api-data-0.3.7.1.orig/src/Web/Internal/FormUrlEncoded.hs 2016-11-14 21:28:23.000000000 +0100 -+++ http-api-data-0.3.7.1/src/Web/Internal/FormUrlEncoded.hs 2017-09-15 11:52:48.979381801 +0200 -@@ -55,6 +55,10 @@ - import Numeric.Natural - #endif - -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup -+#endif -+ - import GHC.Exts (IsList (..), Constraint) - import GHC.Generics - import GHC.TypeLits -@@ -182,7 +186,7 @@ - -- - -- 'Form' can be URL-encoded with 'urlEncodeForm' and URL-decoded with 'urlDecodeForm'. - newtype Form = Form { unForm :: HashMap Text [Text] } -- deriving (Eq, Read, Generic, Monoid) -+ deriving (Eq, Read, Generic, Semigroup, Monoid) - - instance Show Form where - showsPrec d form = showParen (d > 10) $ -Only in http-api-data-0.3.7.1/src/Web/Internal: FormUrlEncoded.hs~ diff --git a/patches/http-api-data-0.3.7.2.patch b/patches/http-api-data-0.3.7.2.patch deleted file mode 100644 index dbe5dffaffdabb4a49f00185a65c94ea289cc02e..0000000000000000000000000000000000000000 --- a/patches/http-api-data-0.3.7.2.patch +++ /dev/null @@ -1,31 +0,0 @@ -diff -ru http-api-data-0.3.7.2.orig/http-api-data.cabal http-api-data-0.3.7.2/http-api-data.cabal ---- http-api-data-0.3.7.2.orig/http-api-data.cabal 2018-01-29 07:02:22.000000000 -0500 -+++ http-api-data-0.3.7.2/http-api-data.cabal 2018-02-04 19:17:07.532057074 -0500 -@@ -46,6 +46,7 @@ - , containers >= 0.5.5.1 && < 0.6 - , hashable >= 1.1.2.4 && < 1.3 - , http-types >= 0.8.6 && < 0.13 -+ , semigroups >= 0.16 && < 0.19 - , text >= 1.1.1.3 && < 1.3 - , time >= 1.4.2 && < 1.9 - , time-locale-compat >= 0.1.1.0 && < 0.2 -diff -ru http-api-data-0.3.7.2.orig/src/Web/Internal/FormUrlEncoded.hs http-api-data-0.3.7.2/src/Web/Internal/FormUrlEncoded.hs ---- http-api-data-0.3.7.2.orig/src/Web/Internal/FormUrlEncoded.hs 2018-01-29 07:02:22.000000000 -0500 -+++ http-api-data-0.3.7.2/src/Web/Internal/FormUrlEncoded.hs 2018-02-04 19:17:52.788058213 -0500 -@@ -39,6 +39,7 @@ - import Data.Map (Map) - import qualified Data.Map as Map - import Data.Monoid -+import qualified Data.Semigroup as Semi - - import Data.Text (Text) - import qualified Data.Text as Text -@@ -182,7 +183,7 @@ - -- - -- 'Form' can be URL-encoded with 'urlEncodeForm' and URL-decoded with 'urlDecodeForm'. - newtype Form = Form { unForm :: HashMap Text [Text] } -- deriving (Eq, Read, Generic, Monoid) -+ deriving (Eq, Read, Generic, Semi.Semigroup, Monoid) - - instance Show Form where - showsPrec d form = showParen (d > 10) $ diff --git a/patches/http-client-0.5.7.0.patch b/patches/http-client-0.5.7.0.patch deleted file mode 100644 index de2b51551e3617210be91f57ad2694db2a977db5..0000000000000000000000000000000000000000 --- a/patches/http-client-0.5.7.0.patch +++ /dev/null @@ -1,51 +0,0 @@ -diff -ru http-client-0.5.7.0.orig/Network/HTTP/Client/Types.hs http-client-0.5.7.0/Network/HTTP/Client/Types.hs ---- http-client-0.5.7.0.orig/Network/HTTP/Client/Types.hs 2017-05-09 13:19:16.000000000 +0200 -+++ http-client-0.5.7.0/Network/HTTP/Client/Types.hs 2017-09-15 12:03:53.567634124 +0200 -@@ -47,6 +47,7 @@ - import Data.Int (Int64) - import Data.Foldable (Foldable) - import Data.Monoid -+import Data.Semigroup - import Data.String (IsString, fromString) - import Data.Time (UTCTime) - import Data.Traversable (Traversable) -@@ -279,16 +280,19 @@ - instance Eq CookieJar where - (==) cj1 cj2 = (DL.sort $ expose cj1) == (DL.sort $ expose cj2) - ---- | Since 1.9 --instance Data.Monoid.Monoid CookieJar where -- mempty = CJ [] -- (CJ a) `mappend` (CJ b) = CJ (DL.nub $ DL.sortBy compare' $ a `mappend` b) -+instance Semigroup CookieJar where -+ (CJ a) <> (CJ b) = CJ (DL.nub $ DL.sortBy compare' $ a `mappend` b) - where compare' c1 c2 = - -- inverse so that recent cookies are kept by nub over older - if cookie_creation_time c1 > cookie_creation_time c2 - then LT - else GT - -+-- | Since 1.9 -+instance Data.Monoid.Monoid CookieJar where -+ mempty = CJ [] -+ mappend = (<>) -+ - -- | Define a HTTP proxy, consisting of a hostname and port number. - - data Proxy = Proxy -@@ -323,9 +327,13 @@ - -- Since 0.4.12 - instance IsString RequestBody where - fromString str = RequestBodyBS (fromString str) -+ - instance Monoid RequestBody where - mempty = RequestBodyBS S.empty -- mappend x0 y0 = -+ mappend = (<>) -+ -+instance Semigroup RequestBody where -+ x0 <> y0 = - case (simplify x0, simplify y0) of - (Left (i, x), Left (j, y)) -> RequestBodyBuilder (i + j) (x `mappend` y) - (Left x, Right y) -> combine (builderToStream x) y -Only in http-client-0.5.7.0/Network/HTTP/Client: Types.hs~ diff --git a/patches/http-client-0.5.8.patch b/patches/http-client-0.5.8.patch deleted file mode 100644 index a682639a267ce670ffc6db0f8d76cc752eeb045b..0000000000000000000000000000000000000000 --- a/patches/http-client-0.5.8.patch +++ /dev/null @@ -1,76 +0,0 @@ -diff --git a/Network/HTTP/Client/Types.hs b/Network/HTTP/Client/Types.hs -index 932660e..60232d1 100644 ---- a/Network/HTTP/Client/Types.hs -+++ b/Network/HTTP/Client/Types.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DeriveDataTypeable #-} - {-# LANGUAGE DeriveFoldable #-} - {-# LANGUAGE DeriveFunctor #-} -@@ -44,7 +45,8 @@ import qualified Data.ByteString.Lazy as L - import Blaze.ByteString.Builder (Builder, fromLazyByteString, fromByteString, toLazyByteString) - import Data.Int (Int64) - import Data.Foldable (Foldable) --import Data.Monoid -+import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.String (IsString, fromString) - import Data.Time (UTCTime) - import Data.Traversable (Traversable) -@@ -277,16 +279,21 @@ instance Ord Cookie where - instance Eq CookieJar where - (==) cj1 cj2 = (DL.sort $ expose cj1) == (DL.sort $ expose cj2) - ---- | Since 1.9 --instance Data.Monoid.Monoid CookieJar where -- mempty = CJ [] -- (CJ a) `mappend` (CJ b) = CJ (DL.nub $ DL.sortBy compare' $ a `mappend` b) -+instance Semigroup CookieJar where -+ (CJ a) <> (CJ b) = CJ (DL.nub $ DL.sortBy compare' $ a <> b) - where compare' c1 c2 = - -- inverse so that recent cookies are kept by nub over older - if cookie_creation_time c1 > cookie_creation_time c2 - then LT - else GT - -+-- | Since 1.9 -+instance Data.Monoid.Monoid CookieJar where -+ mempty = CJ [] -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+ - -- | Define a HTTP proxy, consisting of a hostname and port number. - - data Proxy = Proxy -@@ -323,9 +330,14 @@ instance IsString RequestBody where - fromString str = RequestBodyBS (fromString str) - instance Monoid RequestBody where - mempty = RequestBodyBS S.empty -- mappend x0 y0 = -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+ -+instance Semigroup RequestBody where -+ x0 <> y0 = - case (simplify x0, simplify y0) of -- (Left (i, x), Left (j, y)) -> RequestBodyBuilder (i + j) (x `mappend` y) -+ (Left (i, x), Left (j, y)) -> RequestBodyBuilder (i + j) (x <> y) - (Left x, Right y) -> combine (builderToStream x) y - (Right x, Left y) -> combine x (builderToStream y) - (Right x, Right y) -> combine x y -diff --git a/http-client.cabal b/http-client.cabal -index 0aeb4d7..8ac6b2c 100644 ---- a/http-client.cabal -+++ b/http-client.cabal -@@ -63,6 +63,9 @@ library - else - build-depends: network < 2.6 - -+ if !impl(ghc>=8.0) -+ build-depends: semigroups >= 0.16.1 -+ - if os(mingw32) - build-depends: Win32, safe - diff --git a/patches/inline-c-0.6.0.5.patch b/patches/inline-c-0.6.0.5.patch deleted file mode 100644 index 95a8eb1d04f912a9e5ed5dea263154c7bc4fa9f2..0000000000000000000000000000000000000000 --- a/patches/inline-c-0.6.0.5.patch +++ /dev/null @@ -1,113 +0,0 @@ -diff -ru inline-c-0.6.0.5.orig/inline-c.cabal inline-c-0.6.0.5/inline-c.cabal ---- inline-c-0.6.0.5.orig/inline-c.cabal 2017-08-19 14:10:36.000000000 -0400 -+++ inline-c-0.6.0.5/inline-c.cabal 2018-02-04 15:14:04.043689811 -0500 -@@ -33,13 +33,14 @@ - other-modules: Language.C.Inline.FunPtr - ghc-options: -Wall - build-depends: base >=4.7 && <5 -- , ansi-wl-pprint -+ , ansi-wl-pprint >= 0.6.8 - , bytestring - , containers - , hashable - , mtl - , parsec >= 3 - , parsers -+ , semigroups >= 0.16 - , template-haskell >= 2.12.0.0 - , transformers >= 0.1.3.0 - , unordered-containers -diff -ru inline-c-0.6.0.5.orig/src/Language/C/Inline/Context.hs inline-c-0.6.0.5/src/Language/C/Inline/Context.hs ---- inline-c-0.6.0.5.orig/src/Language/C/Inline/Context.hs 2017-07-23 09:21:45.000000000 -0400 -+++ inline-c-0.6.0.5/src/Language/C/Inline/Context.hs 2018-02-04 14:56:15.955662913 -0500 -@@ -51,7 +51,6 @@ - import Data.Coerce - import Data.Int (Int8, Int16, Int32, Int64) - import qualified Data.Map as Map --import Data.Monoid ((<>)) - import Data.Typeable (Typeable) - import qualified Data.Vector.Storable as V - import qualified Data.Vector.Storable.Mutable as VM -@@ -70,6 +69,10 @@ - import Data.Traversable (traverse) - #endif - -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif -+ - import Language.C.Inline.FunPtr - import qualified Language.C.Types as C - import Language.C.Inline.HaskellIdentifier -@@ -150,6 +153,14 @@ - -- ^ TH.LangC by default - } - -+instance Semigroup Context where -+ ctx2 <> ctx1 = Context -+ { ctxTypesTable = ctxTypesTable ctx1 <> ctxTypesTable ctx2 -+ , ctxAntiQuoters = ctxAntiQuoters ctx1 <> ctxAntiQuoters ctx2 -+ , ctxOutput = ctxOutput ctx1 <|> ctxOutput ctx2 -+ , ctxForeignSrcLang = ctxForeignSrcLang ctx1 <|> ctxForeignSrcLang ctx2 -+ } -+ - instance Monoid Context where - mempty = Context - { ctxTypesTable = mempty -@@ -158,12 +169,9 @@ - , ctxForeignSrcLang = Nothing - } - -- mappend ctx2 ctx1 = Context -- { ctxTypesTable = ctxTypesTable ctx1 <> ctxTypesTable ctx2 -- , ctxAntiQuoters = ctxAntiQuoters ctx1 <> ctxAntiQuoters ctx2 -- , ctxOutput = ctxOutput ctx1 <|> ctxOutput ctx2 -- , ctxForeignSrcLang = ctxForeignSrcLang ctx1 <|> ctxForeignSrcLang ctx2 -- } -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | Context useful to work with vanilla C. Used by default. - -- -diff -ru inline-c-0.6.0.5.orig/src/Language/C/Types.hs inline-c-0.6.0.5/src/Language/C/Types.hs ---- inline-c-0.6.0.5.orig/src/Language/C/Types.hs 2017-07-23 09:21:43.000000000 -0400 -+++ inline-c-0.6.0.5/src/Language/C/Types.hs 2018-02-04 14:56:15.955662913 -0500 -@@ -65,7 +65,6 @@ - import Control.Monad.State (execState, modify) - import Data.List (partition) - import Data.Maybe (fromMaybe) --import Data.Monoid ((<>)) - import Data.Typeable (Typeable) - import Text.PrettyPrint.ANSI.Leijen ((</>), (<+>)) - import qualified Text.PrettyPrint.ANSI.Leijen as PP -@@ -77,6 +76,10 @@ - import Data.Traversable (Traversable) - #endif - -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif -+ - import qualified Language.C.Types.Parse as P - - ------------------------------------------------------------------------ -@@ -103,11 +106,16 @@ - , functionSpecifiers :: [P.FunctionSpecifier] - } deriving (Typeable, Show, Eq) - -+instance Semigroup Specifiers where -+ Specifiers x1 y1 z1 <> Specifiers x2 y2 z2 = -+ Specifiers (x1 ++ x2) (y1 ++ y2) (z1 ++ z2) -+ - instance Monoid Specifiers where - mempty = Specifiers [] [] [] - -- mappend (Specifiers x1 y1 z1) (Specifiers x2 y2 z2) = -- Specifiers (x1 ++ x2) (y1 ++ y2) (z1 ++ z2) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - data Type i - = TypeSpecifier Specifiers TypeSpecifier diff --git a/patches/io-choice-0.0.6.patch b/patches/io-choice-0.0.6.patch deleted file mode 100644 index 09bcd78cb90e498807aa94a0f1ccf4d96412edd4..0000000000000000000000000000000000000000 --- a/patches/io-choice-0.0.6.patch +++ /dev/null @@ -1,42 +0,0 @@ -commit c9daaeb85a1fcd50af24e4fba329670a9ba379b6 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sat Oct 27 21:47:44 2018 -0400 - - Allow building with template-haskell-2.15.0.0 - -diff --git a/Control/Exception/IOChoice/THUtil.hs b/Control/Exception/IOChoice/THUtil.hs -index 46e63f0..f342545 100644 ---- a/Control/Exception/IOChoice/THUtil.hs -+++ b/Control/Exception/IOChoice/THUtil.hs -@@ -24,8 +24,16 @@ checkSupported exc = do - #if __GLASGOW_HASKELL__ >= 800 - DataD _ name [] _ _ _ -> conT name - NewtypeD _ name [] _ _ _ -> conT name -- DataInstD _ name args _ _ _ -> foldl1 appT (conT name:map return args) -- NewtypeInstD _ name args _ _ _ -> foldl1 appT (conT name:map return args) -+ DataInstD _ name -+# if MIN_VERSION_template_haskell(2,15,0) -+ _ -+# endif -+ args _ _ _ -> foldl1 appT (conT name:map return args) -+ NewtypeInstD _ name -+# if MIN_VERSION_template_haskell(2,15,0) -+ _ -+# endif -+ args _ _ _ -> foldl1 appT (conT name:map return args) - #else - DataD _ name [] _ _ -> conT name - NewtypeD _ name [] _ _ -> conT name -@@ -34,7 +42,11 @@ checkSupported exc = do - #endif - TySynD name [] _ -> conT name - #if __GLASGOW_HASKELL__ >= 707 -- TySynInstD name (TySynEqn _ t) -> foldl1 appT (conT name:[return t]) -+ TySynInstD name (TySynEqn -+# if MIN_VERSION_template_haskell(2,15,0) -+ _ -+# endif -+ _ t) -> foldl1 appT (conT name:[return t]) - #else - TySynInstD name args _ -> foldl1 appT (conT name:map return args) - #endif diff --git a/patches/ixset-1.1.patch b/patches/ixset-1.1.patch deleted file mode 100644 index 5217ebdc36bf163cb7f165ed1c7becde2499a986..0000000000000000000000000000000000000000 --- a/patches/ixset-1.1.patch +++ /dev/null @@ -1,20 +0,0 @@ -diff -ru ixset-1.1.orig/src/Data/IxSet/Ix.hs ixset-1.1/src/Data/IxSet/Ix.hs ---- ixset-1.1.orig/src/Data/IxSet/Ix.hs 2018-05-28 12:25:24.000000000 -0400 -+++ ixset-1.1/src/Data/IxSet/Ix.hs 2018-07-04 21:43:13.920339074 -0400 -@@ -24,6 +24,7 @@ - import Data.List (foldl') - import Data.Map (Map) - import qualified Data.Map as Map -+import qualified Data.Map.Strict as MapS - import Data.Set (Set) - import qualified Data.Set as Set - -@@ -66,7 +67,7 @@ - -- 'Map', then a new 'Set' is added transparently. - insert :: (Ord a, Ord k) - => k -> a -> Map k (Set a) -> Map k (Set a) --insert k v index = Map.insertWith' Set.union k (Set.singleton v) index -+insert k v index = MapS.insertWith Set.union k (Set.singleton v) index - - -- | Helper function to 'insert' a list of elements into a set. - insertList :: (Ord a, Ord k) diff --git a/patches/ixset-typed-0.4.patch b/patches/ixset-typed-0.4.patch deleted file mode 100644 index 62ec05292d59dc02f48c3649521d74c882c01cf0..0000000000000000000000000000000000000000 --- a/patches/ixset-typed-0.4.patch +++ /dev/null @@ -1,20 +0,0 @@ -diff -ru ixset-typed-0.4.orig/src/Data/IxSet/Typed/Ix.hs ixset-typed-0.4/src/Data/IxSet/Typed/Ix.hs ---- ixset-typed-0.4.orig/src/Data/IxSet/Typed/Ix.hs 2018-03-18 07:52:09.000000000 -0400 -+++ ixset-typed-0.4/src/Data/IxSet/Typed/Ix.hs 2018-07-04 21:44:42.192341297 -0400 -@@ -27,6 +27,7 @@ - import qualified Data.List as List - import Data.Map (Map) - import qualified Data.Map as Map -+import qualified Data.Map.Strict as MapS - import Data.Set (Set) - import qualified Data.Set as Set - -@@ -80,7 +81,7 @@ - -- 'Map', then a new 'Set' is added transparently. - insert :: (Ord a, Ord k) - => k -> a -> Map k (Set a) -> Map k (Set a) --insert k v index = Map.insertWith' Set.union k (Set.singleton v) index -+insert k v index = MapS.insertWith Set.union k (Set.singleton v) index - - -- | Helper function to 'insert' a list of elements into a set. - insertList :: (Ord a, Ord k) diff --git a/patches/language-c-0.7.1.patch b/patches/language-c-0.7.1.patch deleted file mode 100644 index 763825cb08ba9b5a9acd8f6bdab15bc421634fe7..0000000000000000000000000000000000000000 --- a/patches/language-c-0.7.1.patch +++ /dev/null @@ -1,34 +0,0 @@ -From 03b120c64c12946d134017f4922b55c6ab4f52f8 Mon Sep 17 00:00:00 2001 -From: Kosyrev Serge <serge.kosyrev@iohk.io> -Date: Tue, 16 Jan 2018 02:00:27 +0300 -Subject: [PATCH] Selectively hide Prelude.<>: GHC 8.4 compat - ---- - src/Language/C/Analysis/Debug.hs | 1 + - src/Language/C/Pretty.hs | 1 + - 2 files changed, 2 insertions(+) - -diff --git a/src/Language/C/Analysis/Debug.hs b/src/Language/C/Analysis/Debug.hs -index 9d9670f..4496214 100644 ---- a/src/Language/C/Analysis/Debug.hs -+++ b/src/Language/C/Analysis/Debug.hs -@@ -26,6 +26,7 @@ import Language.C.Analysis.NameSpaceMap - import Language.C.Data - import Language.C.Pretty - -+import Prelude hiding ((<>)) - import Text.PrettyPrint.HughesPJ - import Data.Map (Map) ; import qualified Data.Map as Map - -diff --git a/src/Language/C/Pretty.hs b/src/Language/C/Pretty.hs -index c3c9f48..f87bd90 100644 ---- a/src/Language/C/Pretty.hs -+++ b/src/Language/C/Pretty.hs -@@ -22,6 +22,7 @@ import Data.List (isSuffixOf) - import qualified Data.Set as Set - import Text.PrettyPrint.HughesPJ - import Debug.Trace {- for warnings -} -+import Prelude hiding ((<>)) - - import Language.C.Data - import Language.C.Syntax diff --git a/patches/language-c-0.8.1.patch b/patches/language-c-0.8.1.patch deleted file mode 100644 index 4d097cb9df7887f53a4ade167cda4da2e7389ad1..0000000000000000000000000000000000000000 --- a/patches/language-c-0.8.1.patch +++ /dev/null @@ -1,24 +0,0 @@ -diff -ru language-c-0.8.1.orig/src/Language/C/Analysis/DefTable.hs language-c-0.8.1/src/Language/C/Analysis/DefTable.hs ---- language-c-0.8.1.orig/src/Language/C/Analysis/DefTable.hs 2018-06-08 00:48:29.000000000 -0400 -+++ language-c-0.8.1/src/Language/C/Analysis/DefTable.hs 2018-07-04 21:30:47.308320272 -0400 -@@ -106,7 +106,7 @@ - - -- | get the globally defined entries of a definition table - globalDefs :: DefTable -> GlobalDecls --globalDefs deftbl = Map.foldWithKey insertDecl (GlobalDecls e gtags e) (globalNames $ identDecls deftbl) -+globalDefs deftbl = Map.foldrWithKey insertDecl (GlobalDecls e gtags e) (globalNames $ identDecls deftbl) - where - e = Map.empty - (_fwd_decls,gtags) = Map.mapEither id $ globalNames (tagDecls deftbl) -diff -ru language-c-0.8.1.orig/src/Language/C/Analysis/SemRep.hs language-c-0.8.1/src/Language/C/Analysis/SemRep.hs ---- language-c-0.8.1.orig/src/Language/C/Analysis/SemRep.hs 2018-06-08 00:48:29.000000000 -0400 -+++ language-c-0.8.1/src/Language/C/Analysis/SemRep.hs 2018-07-04 21:30:29.036319812 -0400 -@@ -136,7 +136,7 @@ - ( Map Ident Enumerator, - Map Ident ObjDef, - Map Ident FunDef ) ) --splitIdentDecls include_all = Map.foldWithKey (if include_all then deal else deal') (Map.empty,(Map.empty,Map.empty,Map.empty)) -+splitIdentDecls include_all = Map.foldrWithKey (if include_all then deal else deal') (Map.empty,(Map.empty,Map.empty,Map.empty)) - where - deal ident entry (decls,defs) = (Map.insert ident (declOfDef entry) decls, addDef ident entry defs) - deal' ident (Declaration d) (decls,defs) = (Map.insert ident d decls,defs) diff --git a/patches/language-java-0.2.8.patch b/patches/language-java-0.2.8.patch deleted file mode 100644 index 3787d0f681e41b6e134c371a3da2cefbe8770e31..0000000000000000000000000000000000000000 --- a/patches/language-java-0.2.8.patch +++ /dev/null @@ -1,28 +0,0 @@ -From c5d27e2a64a6ecbe2466ce8867bf834fcea5f79c Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sun, 4 Feb 2018 15:16:11 -0500 -Subject: [PATCH] Fix the build on GHC 8.4 - ---- - Language/Java/Pretty.hs | 4 ++++ - 1 file changed, 4 insertions(+) - -diff --git a/Language/Java/Pretty.hs b/Language/Java/Pretty.hs -index 6986283..558f53e 100644 ---- a/Language/Java/Pretty.hs -+++ b/Language/Java/Pretty.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - module Language.Java.Pretty where - - import Text.PrettyPrint -@@ -7,6 +8,9 @@ import Data.List (intersperse) - - import Language.Java.Syntax - -+#if MIN_VERSION_base(4,11,0) -+import Prelude hiding ((<>)) -+#endif - - prettyPrint :: Pretty a => a -> String - prettyPrint = show . pretty diff --git a/patches/language-javascript-0.6.0.10.patch b/patches/language-javascript-0.6.0.10.patch deleted file mode 100644 index 1cc60a2aaac9dbd8973fd44732fa51759f26dcb1..0000000000000000000000000000000000000000 --- a/patches/language-javascript-0.6.0.10.patch +++ /dev/null @@ -1,48 +0,0 @@ -From dfda491e3c48bdfbba8ae32528a7d1b3a744c38d Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue, 23 Jan 2018 21:57:09 -0500 -Subject: [PATCH] Fix the build with GHC 8.4.1 - ---- - language-javascript.cabal | 3 +++ - src/Language/JavaScript/Pretty/Printer.hs | 6 ++---- - 2 files changed, 5 insertions(+), 4 deletions(-) - -diff --git a/language-javascript.cabal b/language-javascript.cabal -index 3a3092b..c18e016 100644 ---- a/language-javascript.cabal -+++ b/language-javascript.cabal -@@ -36,6 +36,9 @@ Library - , bytestring >= 0.9.1 - , text >= 1.2 - , utf8-string >= 0.3.7 && < 2 -+ if !impl(ghc>=8.0) -+ build-depends: semigroups >= 0.16.1 -+ - if impl(ghc >= 7.10) - build-tools: happy >= 1.19, alex >= 3.1.4 - else -diff --git a/src/Language/JavaScript/Pretty/Printer.hs b/src/Language/JavaScript/Pretty/Printer.hs -index cc2ea36..fd1fbe6 100644 ---- a/src/Language/JavaScript/Pretty/Printer.hs -+++ b/src/Language/JavaScript/Pretty/Printer.hs -@@ -10,7 +10,8 @@ module Language.JavaScript.Pretty.Printer - - import Blaze.ByteString.Builder (Builder, toLazyByteString) - import Data.List --import Data.Monoid (mappend, mempty) -+import Data.Monoid (mempty) -+import Data.Semigroup ((<>)) - import Data.Text.Lazy (Text) - import Language.JavaScript.Parser.AST - import Language.JavaScript.Parser.SrcLocation -@@ -27,9 +28,6 @@ data PosAccum = PosAccum (Int, Int) Builder - -- --------------------------------------------------------------------- - -- Pretty printer stuff via blaze-builder - --(<>) :: Builder -> Builder -> Builder --(<>) = mappend -- - str :: String -> Builder - str = BS.fromString - diff --git a/patches/lens-4.15.4.patch b/patches/lens-4.15.4.patch deleted file mode 100644 index 9b2bcb356b265d0cd0b16c532abbf148b252742a..0000000000000000000000000000000000000000 --- a/patches/lens-4.15.4.patch +++ /dev/null @@ -1,107 +0,0 @@ -diff -ru lens-4.15.4.orig/src/Control/Lens/Indexed.hs lens-4.15.4/src/Control/Lens/Indexed.hs ---- lens-4.15.4.orig/src/Control/Lens/Indexed.hs 2017-08-03 09:08:05.000000000 +0200 -+++ lens-4.15.4/src/Control/Lens/Indexed.hs 2017-09-17 11:27:39.341165493 +0200 -@@ -406,7 +406,7 @@ - -- @ - -- 'mapM_' ≡ 'imapM' '.' 'const' - -- @ --imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m () -+imapM_ :: (FoldableWithIndex i t, Applicative m, Monad m) => (i -> a -> m b) -> t a -> m () - imapM_ f = liftM skip . getSequenced #. ifoldMap (\i -> Sequenced #. f i) - {-# INLINE imapM_ #-} - -diff -ru lens-4.15.4.orig/src/Control/Lens/Internal/Fold.hs lens-4.15.4/src/Control/Lens/Internal/Fold.hs ---- lens-4.15.4.orig/src/Control/Lens/Internal/Fold.hs 2017-08-03 09:08:05.000000000 +0200 -+++ lens-4.15.4/src/Control/Lens/Internal/Fold.hs 2017-09-17 11:27:39.341165493 +0200 -@@ -53,8 +53,8 @@ - -- | A 'Monoid' for a 'Contravariant' 'Applicative'. - newtype Folding f a = Folding { getFolding :: f a } - --instance (Contravariant f, Apply f) => Semigroup (Folding f a) where -- Folding fr <> Folding fs = Folding (fr .> fs) -+instance (Contravariant f, Applicative f) => Semigroup (Folding f a) where -+ Folding fr <> Folding fs = Folding (fr *> fs) - {-# INLINE (<>) #-} - - instance (Contravariant f, Applicative f) => Monoid (Folding f a) where -@@ -72,8 +72,8 @@ - -- The argument 'a' of the result should not be used! - newtype Traversed a f = Traversed { getTraversed :: f a } - --instance Apply f => Semigroup (Traversed a f) where -- Traversed ma <> Traversed mb = Traversed (ma .> mb) -+instance Applicative f => Semigroup (Traversed a f) where -+ Traversed ma <> Traversed mb = Traversed (ma *> mb) - {-# INLINE (<>) #-} - - instance Applicative f => Monoid (Traversed a f) where -@@ -91,11 +91,11 @@ - -- The argument 'a' of the result should not be used! - newtype Sequenced a m = Sequenced { getSequenced :: m a } - --instance Apply m => Semigroup (Sequenced a m) where -- Sequenced ma <> Sequenced mb = Sequenced (ma .> mb) -+instance Applicative m => Semigroup (Sequenced a m) where -+ Sequenced ma <> Sequenced mb = Sequenced (ma *> mb) - {-# INLINE (<>) #-} - --instance Monad m => Monoid (Sequenced a m) where -+instance (Applicative m, Monad m) => Monoid (Sequenced a m) where - mempty = Sequenced (return (error "Sequenced: value used")) - {-# INLINE mempty #-} - Sequenced ma `mappend` Sequenced mb = Sequenced (ma >> mb) -diff -ru lens-4.15.4.orig/src/Control/Lens/Internal/Zoom.hs lens-4.15.4/src/Control/Lens/Internal/Zoom.hs ---- lens-4.15.4.orig/src/Control/Lens/Internal/Zoom.hs 2017-08-03 09:08:05.000000000 +0200 -+++ lens-4.15.4/src/Control/Lens/Internal/Zoom.hs 2017-09-17 11:27:39.341165493 +0200 -@@ -291,7 +291,7 @@ - Effect ma <> Effect mb = Effect (liftF2 (<>) ma mb) - {-# INLINE (<>) #-} - --instance (Monad m, Monoid r) => Monoid (Effect m r a) where -+instance (Apply m, Monad m, Monoid r) => Monoid (Effect m r a) where - mempty = Effect (return mempty) - {-# INLINE mempty #-} - Effect ma `mappend` Effect mb = Effect (liftM2 mappend ma mb) -diff --git a/src/Language/Haskell/TH/Lens.hs b/src/Language/Haskell/TH/Lens.hs -index a38dd07d..c69b6ce4 100644 ---- a/src/Language/Haskell/TH/Lens.hs -+++ b/src/Language/Haskell/TH/Lens.hs -@@ -230,8 +230,13 @@ module Language.Haskell.TH.Lens - -- ** FunDep Prisms TODO make a lens - , _FunDep - -- ** FamFlavour Prisms -+#if MIN_VERSION_template_haskell(2,9,0) -+ -- | These are not available in GHC >= 8.4.1. -+#else -+ -- | Note that these have been removed in GHC >= 8.4.1. - , _TypeFam - , _DataFam -+#endif - -- ** FixityDirection Prisms - , _InfixL - , _InfixR -@@ -1689,6 +1694,8 @@ _FunDep - reviewer (x, y) = FunDep x y - remitter (FunDep x y) = (x, y) - -+#if !MIN_VERSION_template_haskell(2,13,0) -+-- | Removed in GHC 8.4. - _TypeFam :: Prism' FamFlavour () - _TypeFam - = prism' reviewer remitter -@@ -1697,6 +1704,7 @@ _TypeFam - remitter TypeFam = Just () - remitter _ = Nothing - -+-- | Removed in GHC 8.4. - _DataFam :: Prism' FamFlavour () - _DataFam - = prism' reviewer remitter -@@ -1704,6 +1712,7 @@ _DataFam - reviewer () = DataFam - remitter DataFam = Just () - remitter _ = Nothing -+#endif - - #if MIN_VERSION_template_haskell(2,9,0) - tySynEqnPatterns :: Lens' TySynEqn [Type] diff --git a/patches/llvm-hs-5.1.0.patch b/patches/llvm-hs-5.1.0.patch deleted file mode 100644 index 83b4cafa9cfe2ca647bfb94c83b1a8fdac8964d5..0000000000000000000000000000000000000000 --- a/patches/llvm-hs-5.1.0.patch +++ /dev/null @@ -1,25 +0,0 @@ -diff --git llvm-hs/Setup.hs llvm-hs/Setup.hs -index fe7daf4..7bf1729 100644 ---- llvm-hs/Setup.hs -+++ llvm-hs/Setup.hs -@@ -35,6 +35,11 @@ mkFlagName :: String -> FlagName - mkFlagName = FlagName - #endif - -+#if !MIN_VERSION_Cabal(2,1,0) -+lookupFlagAssignment :: FlagName -> FlagAssignment -> Maybe Bool -+lookupFlagAssignment = lookup -+#endif -+ - llvmVersion :: Version - llvmVersion = mkVersion [5,0] - -@@ -125,7 +130,7 @@ main = do - [llvmVersion] <- liftM lines $ llvmConfig ["--version"] - let getLibs = liftM (map (fromJust . stripPrefix "-l") . words) . llvmConfig - flags = configConfigurationsFlags confFlags -- linkFlag = case lookup (mkFlagName "shared-llvm") flags of -+ linkFlag = case lookupFlagAssignment (mkFlagName "shared-llvm") flags of - Nothing -> "--link-shared" - Just shared -> if shared then "--link-shared" else "--link-static" - libs <- getLibs ["--libs", linkFlag] diff --git a/patches/llvm-hs-5.1.3.patch b/patches/llvm-hs-5.1.3.patch deleted file mode 100644 index 1ffc8b8c9528f6d7e9e37785939331cae2a41be4..0000000000000000000000000000000000000000 --- a/patches/llvm-hs-5.1.3.patch +++ /dev/null @@ -1,25 +0,0 @@ -diff --git a/Setup.hs b/Setup.hs -index fe7daf4..e987894 100644 ---- a/Setup.hs -+++ b/Setup.hs -@@ -35,6 +35,11 @@ mkFlagName :: String -> FlagName - mkFlagName = FlagName - #endif - -+#if !(MIN_VERSION_Cabal(2,1,0)) -+lookupFlagAssignment :: FlagName -> FlagAssignment -> Maybe Bool -+lookupFlagAssignment = lookup -+#endif -+ - llvmVersion :: Version - llvmVersion = mkVersion [5,0] - -@@ -125,7 +130,7 @@ main = do - [llvmVersion] <- liftM lines $ llvmConfig ["--version"] - let getLibs = liftM (map (fromJust . stripPrefix "-l") . words) . llvmConfig - flags = configConfigurationsFlags confFlags -- linkFlag = case lookup (mkFlagName "shared-llvm") flags of -+ linkFlag = case lookupFlagAssignment (mkFlagName "shared-llvm") flags of - Nothing -> "--link-shared" - Just shared -> if shared then "--link-shared" else "--link-static" - libs <- getLibs ["--libs", linkFlag] diff --git a/patches/llvm-hs-pure-5.1.2.patch b/patches/llvm-hs-pure-5.1.2.patch deleted file mode 100644 index 2436de69e2d2c65bd39e52c199862523c0e85b29..0000000000000000000000000000000000000000 --- a/patches/llvm-hs-pure-5.1.2.patch +++ /dev/null @@ -1,29 +0,0 @@ -diff --git a/src/LLVM/IRBuilder/Internal/SnocList.hs b/src/LLVM/IRBuilder/Internal/SnocList.hs -index 18a3ab7..432391d 100644 ---- a/src/LLVM/IRBuilder/Internal/SnocList.hs -+++ b/src/LLVM/IRBuilder/Internal/SnocList.hs -@@ -1,12 +1,23 @@ -+{-# LANGUAGE CPP #-} - module LLVM.IRBuilder.Internal.SnocList where - -+#if MIN_VERSION_base(4,11,0) - import LLVM.Prelude -+#else -+import Data.Semigroup (Semigroup(..)) -+import LLVM.Prelude hiding ((<>)) -+#endif - - newtype SnocList a = SnocList { unSnocList :: [a] } - deriving (Eq, Show) - -+instance Semigroup (SnocList a) where -+ SnocList xs <> SnocList ys = SnocList $ ys ++ xs -+ - instance Monoid (SnocList a) where -- mappend (SnocList xs) (SnocList ys) = SnocList $ ys ++ xs -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - mempty = SnocList [] - - snoc :: SnocList a -> a -> SnocList a diff --git a/patches/log-domain-0.11.2.patch b/patches/log-domain-0.11.2.patch deleted file mode 100644 index 1d69af8a1e27566f4a4b4d5a106232ed041a105a..0000000000000000000000000000000000000000 --- a/patches/log-domain-0.11.2.patch +++ /dev/null @@ -1,239 +0,0 @@ -diff -ru log-domain-0.11.2.orig/log-domain.cabal log-domain-0.11.2/log-domain.cabal ---- log-domain-0.11.2.orig/log-domain.cabal 2017-07-29 01:42:50.000000000 +0200 -+++ log-domain-0.11.2/log-domain.cabal 2017-09-17 11:17:06.004639027 +0200 -@@ -1,92 +1,93 @@ --name: log-domain --category: Numeric --version: 0.11.2 --license: BSD3 --cabal-version: >= 1.8 --license-file: LICENSE --author: Edward A. Kmett --maintainer: Edward A. Kmett <ekmett@gmail.com> --stability: provisional --homepage: http://github.com/ekmett/log-domain/ --bug-reports: http://github.com/ekmett/log-domain/issues --copyright: Copyright (C) 2013-2015 Edward A. Kmett --build-type: Custom --tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.3, GHC == 8.0.2 --synopsis: Log-domain arithmetic --description: This package provides log-domain floats, doubles and complex numbers. -- --extra-source-files: -- .travis.yml -- .ghci -- .gitignore -- .vim.custom -- travis/cabal-apt-install -- travis/config -- AUTHORS.markdown -- README.markdown -- CHANGELOG.markdown -- HLint.hs -- Warning.hs -- --source-repository head -- type: git -- location: https://github.com/analytics/log-domain -- --custom-setup -- setup-depends: -- base >= 4 && < 5, -- Cabal, -- cabal-doctest >= 1 && < 1.1 -- ---- You can disable the doctests test suite with -f-test-doctests --flag test-doctests -- default: True -- manual: True -- --flag ffi -- default: True -- manual: True -- --library -- build-depends: -- base >= 4.5 && < 5, -- binary >= 0.5 && < 0.9, -- bytes >= 0.7 && < 1, -- cereal >= 0.3.5 && < 0.6, -- comonad >= 4 && < 6, -- deepseq >= 1.3 && < 1.5, -- distributive >= 0.3 && < 1, -- hashable >= 1.2.5 && < 1.3, -- semigroupoids >= 4 && < 6, -- semigroups >= 0.8.4 && < 1, -- safecopy >= 0.8.1 && < 0.10, -- vector >= 0.9 && < 0.13 -- -- exposed-modules: -- Numeric.Log Numeric.Log.Signed -- -- if impl(ghc < 7.6) -- build-depends: ghc-prim -- -- if flag(ffi) && !(os(windows) && !impl(ghc >= 8.0)) -- cpp-options: -D__USE_FFI__ -- -- ghc-options: -Wall -fwarn-tabs -O2 -- hs-source-dirs: src -- --test-suite doctests -- type: exitcode-stdio-1.0 -- main-is: doctests.hs -- ghc-options: -Wall -threaded -- hs-source-dirs: tests -- -- if !flag(test-doctests) -- buildable: False -- else -- build-depends: -- base, -- doctest >= 0.11.1 && < 0.13, -- generic-deriving, -- log-domain, -- semigroups >= 0.9, -- simple-reflect >= 0.3.1 -+name: log-domain -+category: Numeric -+version: 0.11.2 -+x-revision: 1 -+license: BSD3 -+cabal-version: >= 1.8 -+license-file: LICENSE -+author: Edward A. Kmett -+maintainer: Edward A. Kmett <ekmett@gmail.com> -+stability: provisional -+homepage: http://github.com/ekmett/log-domain/ -+bug-reports: http://github.com/ekmett/log-domain/issues -+copyright: Copyright (C) 2013-2015 Edward A. Kmett -+build-type: Custom -+tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.3, GHC == 8.0.2 -+synopsis: Log-domain arithmetic -+description: This package provides log-domain floats, doubles and complex numbers. -+ -+extra-source-files: -+ .travis.yml -+ .ghci -+ .gitignore -+ .vim.custom -+ travis/cabal-apt-install -+ travis/config -+ AUTHORS.markdown -+ README.markdown -+ CHANGELOG.markdown -+ HLint.hs -+ Warning.hs -+ -+source-repository head -+ type: git -+ location: https://github.com/analytics/log-domain -+ -+custom-setup -+ setup-depends: -+ base >= 4 && < 5, -+ Cabal, -+ cabal-doctest >= 1 && < 1.1 -+ -+-- You can disable the doctests test suite with -f-test-doctests -+flag test-doctests -+ default: True -+ manual: True -+ -+flag ffi -+ default: True -+ manual: True -+ -+library -+ build-depends: -+ base >= 4.5 && < 5, -+ binary >= 0.5 && < 0.9, -+ bytes >= 0.7 && < 1, -+ cereal >= 0.3.5 && < 0.6, -+ comonad >= 4 && < 6, -+ deepseq >= 1.3 && < 1.5, -+ distributive >= 0.3 && < 1, -+ hashable >= 1.2.5 && < 1.3, -+ semigroupoids >= 4 && < 6, -+ semigroups >= 0.8.4 && < 1, -+ safecopy >= 0.8.1 && < 0.10, -+ vector >= 0.9 && < 0.13 -+ -+ exposed-modules: -+ Numeric.Log Numeric.Log.Signed -+ -+ if impl(ghc < 7.6) -+ build-depends: ghc-prim -+ -+ if flag(ffi) && !(os(windows) && !impl(ghc >= 8.0)) -+ cpp-options: -D__USE_FFI__ -+ -+ ghc-options: -Wall -fwarn-tabs -O2 -+ hs-source-dirs: src -+ -+test-suite doctests -+ type: exitcode-stdio-1.0 -+ main-is: doctests.hs -+ ghc-options: -Wall -threaded -+ hs-source-dirs: tests -+ -+ if !flag(test-doctests) -+ buildable: False -+ else -+ build-depends: -+ base, -+ doctest >= 0.11.1 && < 0.14, -+ generic-deriving, -+ log-domain, -+ semigroups >= 0.9, -+ simple-reflect >= 0.3.1 -diff -ru log-domain-0.11.2.orig/src/Numeric/Log.hs log-domain-0.11.2/src/Numeric/Log.hs ---- log-domain-0.11.2.orig/src/Numeric/Log.hs 2017-07-29 01:42:50.000000000 +0200 -+++ log-domain-0.11.2/src/Numeric/Log.hs 2017-09-17 11:17:38.284451478 +0200 -@@ -41,9 +41,8 @@ - import Data.Hashable.Lifted - import Data.Int - import Data.List as List hiding (sum) --#if __GLASGOW_HASKELL__ < 710 --import Data.Monoid --#endif -+import Data.List.NonEmpty (NonEmpty(..)) -+import Data.Semigroup - import Data.SafeCopy - import Data.Semigroup.Foldable - import Data.Semigroup.Traversable -@@ -421,20 +420,26 @@ - - data Acc1 a = Acc1 {-# UNPACK #-} !Int64 !a - --instance (Precise a, RealFloat a) => Monoid (Log a) where -- mempty = Exp negInf -- {-# INLINE mempty #-} -- mappend = (+) -- {-# INLINE mappend #-} -- mconcat [] = 0 -- mconcat (Exp z:zs) = Exp $ case List.foldl' step1 (Acc1 0 z) zs of -+instance (Precise a, RealFloat a) => Semigroup (Log a) where -+ (<>) = (+) -+ {-# INLINE (<>) #-} -+ sconcat (Exp z :| zs) = Exp $ case List.foldl' step1 (Acc1 0 z) zs of - Acc1 nm1 a - | isInfinite a -> a - | otherwise -> a + log1p (List.foldl' (step2 a) 0 zs + fromIntegral nm1) - where - step1 (Acc1 n y) (Exp x) = Acc1 (n + 1) (max x y) - step2 a r (Exp x) = r + expm1 (x - a) -- {-# INLINE mconcat #-} -+ {-# INLINE sconcat #-} -+ -+instance (Precise a, RealFloat a) => Monoid (Log a) where -+ mempty = Exp negInf -+ {-# INLINE mempty #-} -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+ mconcat [] = 0 -+ mconcat (x:xs) = sconcat (x :| xs) - - logMap :: Floating a => (a -> a) -> Log a -> Log a - logMap f = Exp . log . f . exp . ln diff --git a/patches/managed-1.0.5.patch b/patches/managed-1.0.5.patch deleted file mode 100644 index 0b7f52b8b4154db7156bd3a120b1505ab3af299f..0000000000000000000000000000000000000000 --- a/patches/managed-1.0.5.patch +++ /dev/null @@ -1,30 +0,0 @@ -diff -ru managed-1.0.5.orig/src/Control/Monad/Managed.hs managed-1.0.5/src/Control/Monad/Managed.hs ---- managed-1.0.5.orig/src/Control/Monad/Managed.hs 2016-05-29 02:12:29.000000000 +0200 -+++ managed-1.0.5/src/Control/Monad/Managed.hs 2017-09-14 22:31:21.404647462 +0200 -@@ -110,6 +110,10 @@ - import Control.Monad.IO.Class (MonadIO(liftIO)) - import Control.Monad.Trans.Class (lift) - -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif -+ - #if MIN_VERSION_base(4,8,0) - import Control.Applicative (liftA2) - #else -@@ -162,10 +166,12 @@ - a <- m - return_ a ) - -+instance Monoid a => Semigroup (Managed a) where -+ (<>) = liftA2 mappend -+ - instance Monoid a => Monoid (Managed a) where - mempty = pure mempty -- -- mappend = liftA2 mappend -+ mappend = (<>) - - instance Num a => Num (Managed a) where - fromInteger = pure . fromInteger -Only in managed-1.0.5/src/Control/Monad: Managed.hs~ diff --git a/patches/map-syntax-0.2.0.2.patch b/patches/map-syntax-0.2.0.2.patch deleted file mode 100644 index 671c7fd8dbeddd0ebd47e9d121a5b21861747a84..0000000000000000000000000000000000000000 --- a/patches/map-syntax-0.2.0.2.patch +++ /dev/null @@ -1,98 +0,0 @@ -From 72aa55320720c4dd2c5e0446690d78fab48eaf24 Mon Sep 17 00:00:00 2001 -From: Herbert Valerio Riedel <hvr@gnu.org> -Date: Sat, 3 Jun 2017 11:28:22 +0200 -Subject: [PATCH] Forward-compat with Monoid/Semigroup proposal - -NB: This requires a minor version bump as a new instance for -`Semigroup` gets introduced. ---- - map-syntax.cabal | 24 +++++++++++++++--------- - src/Data/Map/Syntax.hs | 11 +++++++---- - 2 files changed, 22 insertions(+), 13 deletions(-) - -diff --git a/map-syntax.cabal b/map-syntax.cabal -index 6feeed4..3f30ccf 100644 ---- a/map-syntax.cabal -+++ b/map-syntax.cabal -@@ -21,7 +21,6 @@ extra-source-files: - README.md, - runCoverage.sh - -- - Library - hs-source-dirs: src - default-language: Haskell2010 -@@ -29,18 +28,18 @@ Library - exposed-modules: - Data.Map.Syntax - -- - build-depends: -- base >= 4 && < 5, -+ base >= 4.3 && < 5, - containers >= 0.3 && < 0.6, - mtl >= 2.0 && < 2.3 - -- if impl(ghc >= 6.12.0) -- ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -- -fno-warn-unused-do-bind -- else -- ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -+ ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -fno-warn-unused-do-bind - -+ -- See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0#base-4.9.0.0 -+ if impl(ghc >= 8.0) -+ ghc-options: -Wcompat -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances -+ else -+ build-depends: semigroups == 0.18.* - - source-repository head - type: git -@@ -56,8 +55,15 @@ Test-suite testsuite - default-language: Haskell2010 - - ghc-options: -Wall -fwarn-tabs -+ -+ -- See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0#base-4.9.0.0 -+ if impl(ghc >= 8.0) -+ ghc-options: -Wcompat -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances -+ else -+ build-depends: semigroups == 0.18.* -+ - build-depends: -- base >= 4 && < 5, -+ base >= 4.3 && < 5, - containers >= 0.3 && < 0.6, - deepseq >= 1.3 && < 2, - HUnit >= 1.2 && < 2, -diff --git a/src/Data/Map/Syntax.hs b/src/Data/Map/Syntax.hs -index fc746b9..7b22956 100644 ---- a/src/Data/Map/Syntax.hs -+++ b/src/Data/Map/Syntax.hs -@@ -52,8 +52,8 @@ import qualified Data.Map as M - - #if !MIN_VERSION_base(4,8,0) - import Control.Applicative --import Data.Monoid - #endif -+import Data.Semigroup - ------------------------------------------------------------------------------ - - -@@ -92,10 +92,13 @@ newtype MapSyntaxM k v a = MapSyntaxM { unMapSyntax :: State (MapRep k v) a } - - - ------------------------------------------------------------------------------ --instance Monoid (MapSyntax k v) where -- mempty = return $! () -- mappend = (>>) - -+instance Semigroup (MapSyntax k v) where -+ (<>) = (>>) -+ -+instance Monoid (MapSyntax k v) where -+ mempty = pure $! () -+ mappend = (<>) - - ------------------------------------------------------------------------------ - -- | Convenient type alias that will probably be used most of the time. diff --git a/patches/memory-0.14.16.patch b/patches/memory-0.14.16.patch deleted file mode 100644 index be760ac762e6eef753ab58e4206070362db765cf..0000000000000000000000000000000000000000 --- a/patches/memory-0.14.16.patch +++ /dev/null @@ -1,14 +0,0 @@ -diff -ru memory-0.14.16.orig/Data/ByteArray/Sized.hs memory-0.14.16/Data/ByteArray/Sized.hs ---- memory-0.14.16.orig/Data/ByteArray/Sized.hs 2018-02-26 05:46:08.000000000 -0500 -+++ memory-0.14.16/Data/ByteArray/Sized.hs 2018-06-24 17:59:32.450242598 -0400 -@@ -21,7 +21,9 @@ - {-# LANGUAGE MultiParamTypeClasses #-} - {-# LANGUAGE FunctionalDependencies #-} - {-# LANGUAGE UndecidableInstances #-} -- -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - module Data.ByteArray.Sized - ( ByteArrayN(..) - , SizedByteArray diff --git a/patches/memory-0.14.8.patch b/patches/memory-0.14.8.patch deleted file mode 100644 index dd7185c703bc25a6d7399a2fb4fce85289a6ac1d..0000000000000000000000000000000000000000 --- a/patches/memory-0.14.8.patch +++ /dev/null @@ -1,52 +0,0 @@ -diff -ru memory-0.14.8.orig/Data/ByteArray/Bytes.hs memory-0.14.8/Data/ByteArray/Bytes.hs ---- memory-0.14.8.orig/Data/ByteArray/Bytes.hs 2017-09-04 16:13:06.000000000 +0200 -+++ memory-0.14.8/Data/ByteArray/Bytes.hs 2017-09-15 12:14:25.768075696 +0200 -@@ -23,6 +23,7 @@ - import Data.Memory.Internal.CompatPrim - import Data.Memory.Internal.Compat (unsafeDoIO) - import Data.ByteArray.Types -+import Data.Semigroup - - -- | Simplest Byte Array - data Bytes = Bytes (MutableByteArray# RealWorld) -@@ -33,9 +34,12 @@ - (==) = bytesEq - instance Ord Bytes where - compare = bytesCompare -+ -+instance Semigroup Bytes where -+ b1 <> b2 = unsafeDoIO $ bytesAppend b1 b2 - instance Monoid Bytes where - mempty = unsafeDoIO (newBytes 0) -- mappend b1 b2 = unsafeDoIO $ bytesAppend b1 b2 -+ mappend = (<>) - mconcat = unsafeDoIO . bytesConcat - instance NFData Bytes where - rnf b = b `seq` () -Only in memory-0.14.8/Data/ByteArray: Bytes.hs~ -diff -ru memory-0.14.8.orig/Data/ByteArray/ScrubbedBytes.hs memory-0.14.8/Data/ByteArray/ScrubbedBytes.hs ---- memory-0.14.8.orig/Data/ByteArray/ScrubbedBytes.hs 2017-04-25 12:46:48.000000000 +0200 -+++ memory-0.14.8/Data/ByteArray/ScrubbedBytes.hs 2017-09-15 12:13:32.248375591 +0200 -@@ -25,6 +25,7 @@ - import Data.Memory.Internal.Scrubber (getScrubber) - import Data.ByteArray.Types - import Foreign.Storable -+import Data.Semigroup - - -- | ScrubbedBytes is a memory chunk which have the properties of: - -- -@@ -43,9 +44,11 @@ - (==) = scrubbedBytesEq - instance Ord ScrubbedBytes where - compare = scrubbedBytesCompare -+instance Semigroup ScrubbedBytes where -+ b1 <> b2 = unsafeDoIO $ scrubbedBytesAppend b1 b2 - instance Monoid ScrubbedBytes where - mempty = unsafeDoIO (newScrubbedBytes 0) -- mappend b1 b2 = unsafeDoIO $ scrubbedBytesAppend b1 b2 -+ mappend = (<>) - mconcat = unsafeDoIO . scrubbedBytesConcat - instance NFData ScrubbedBytes where - rnf b = b `seq` () -Only in memory-0.14.8/Data/ByteArray: ScrubbedBytes.hs~ -Only in memory-0.14.8/Data/ByteArray: Types.hs~ diff --git a/patches/microlens-0.4.8.1.patch b/patches/microlens-0.4.8.1.patch deleted file mode 100644 index 673e7754f945fa81d4730dfba656cb6f0577f980..0000000000000000000000000000000000000000 --- a/patches/microlens-0.4.8.1.patch +++ /dev/null @@ -1,20 +0,0 @@ -diff -ru microlens-0.4.8.1.orig/src/Lens/Micro.hs microlens-0.4.8.1/src/Lens/Micro.hs ---- microlens-0.4.8.1.orig/src/Lens/Micro.hs 2017-08-11 20:23:02.000000000 +0200 -+++ microlens-0.4.8.1/src/Lens/Micro.hs 2017-09-17 12:39:28.310024297 +0200 -@@ -1270,10 +1270,14 @@ - - newtype Traversed a f = Traversed { getTraversed :: f a } - -+instance Applicative f => Semigroup (Traversed a f) where -+ Traversed ma <> Traversed mb = Traversed (ma *> mb) -+ {-# INLINE (<>) #-} -+ - instance Applicative f => Monoid (Traversed a f) where - mempty = Traversed (pure (error "Lens.Micro.Traversed: value used")) - {-# INLINE mempty #-} -- Traversed ma `mappend` Traversed mb = Traversed (ma *> mb) -+ mappend = (<>) - {-# INLINE mappend #-} - - newtype Bazaar a b t = Bazaar (forall f. Applicative f => (a -> f b) -> f t) -Only in microlens-0.4.8.1/src/Lens: Micro.hs~ diff --git a/patches/monoid-extras-0.4.2.patch b/patches/monoid-extras-0.4.2.patch deleted file mode 100644 index 37ae584675ac8eb89a412d644e6912ac854e683a..0000000000000000000000000000000000000000 --- a/patches/monoid-extras-0.4.2.patch +++ /dev/null @@ -1,137 +0,0 @@ -commit 34e9ea57bcc89746139da45500ca1d338ab40022 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 10:46:51 2018 -0500 - - Fix the build with GHC 8.4 - -diff --git a/benchmarks/SemiDirectProduct.hs b/benchmarks/SemiDirectProduct.hs -index 478fa3d..3c30995 100644 ---- a/benchmarks/SemiDirectProduct.hs -+++ b/benchmarks/SemiDirectProduct.hs -@@ -13,12 +13,15 @@ import Data.Word - #else - import Data.Monoid (Sum(..)) - #endif -+#if !MIN_VERSION_base(4,11,0) -+import Data.Semigroup (Semigroup) -+#endif - - import Data.Monoid.Action - import qualified Data.Monoid.SemiDirectProduct as L - import qualified Data.Monoid.SemiDirectProduct.Strict as S - --newtype MyMonoid = MyMonoid (Sum Word) deriving Monoid -+newtype MyMonoid = MyMonoid (Sum Word) deriving (Semigroup, Monoid) - - instance Action MyMonoid () where - act _ = id -diff --git a/src/Data/Monoid/Endomorphism.hs b/src/Data/Monoid/Endomorphism.hs -index 0e130d1..aeeda35 100644 ---- a/src/Data/Monoid/Endomorphism.hs -+++ b/src/Data/Monoid/Endomorphism.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE FlexibleContexts #-} - {-# LANGUAGE StandaloneDeriving #-} - {-# LANGUAGE UndecidableInstances #-} -@@ -20,7 +21,8 @@ module Data.Monoid.Endomorphism - import Control.Category - import Data.Group - import Data.Groupoid --import Data.Semigroup -+import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.Semigroupoid - import Prelude (Show) - -@@ -35,9 +37,11 @@ deriving instance Show (k a a) => Show (Endomorphism k a) - instance Semigroupoid k => Semigroup (Endomorphism k a) where - Endomorphism a <> Endomorphism b = Endomorphism (a `o` b) - --instance Category k => Monoid (Endomorphism k a) where -+instance (Semigroupoid k, Category k) => Monoid (Endomorphism k a) where - mempty = Endomorphism id -+#if !MIN_VERSION_base(4,11,0) - Endomorphism a `mappend` Endomorphism b = Endomorphism (a . b) -+#endif - - instance (Category k, Groupoid k) => Group (Endomorphism k a) where - invert (Endomorphism a) = Endomorphism (inv a) -diff --git a/src/Data/Monoid/SemiDirectProduct.hs b/src/Data/Monoid/SemiDirectProduct.hs -index ee8a4d6..e9b08db 100644 ---- a/src/Data/Monoid/SemiDirectProduct.hs -+++ b/src/Data/Monoid/SemiDirectProduct.hs -@@ -8,8 +8,9 @@ module Data.Monoid.SemiDirectProduct - ) where - - #if !MIN_VERSION_base(4,8,0) --import Data.Monoid -+import Data.Monoid (Monoid(..)) - #endif -+import Data.Semigroup (Semigroup(..)) - - import Data.Monoid.Action - -@@ -29,16 +30,27 @@ import Data.Monoid.Action - -- quotient. - newtype Semi s m = Semi { unSemi :: (s,m) } - -+instance (Semigroup m, Semigroup s, Action m s) => Semigroup (Semi s m) where -+ x <> y = Semi (xs <> (xm `act` ys), xm <> ym) -+ where (xs, xm) = unSemi x -+ (ys, ym) = unSemi y -+ {-# INLINE (<>) #-} -+ -+ sconcat = foldr1 (<>) -+ {-# INLINE sconcat #-} - - instance (Monoid m, Monoid s, Action m s) => Monoid (Semi s m) where - mempty = Semi (mempty, mempty) - {-# INLINE mempty #-} - -+#if !MIN_VERSION_base(4,11,0) - mappend x y = Semi (xs `mappend` (xm `act` ys), xm `mappend` ym) - where (xs, xm) = unSemi x - (ys, ym) = unSemi y - - {-# INLINE mappend #-} -+#endif -+ - mconcat = foldr mappend mempty - {-# INLINE mconcat #-} - -diff --git a/src/Data/Monoid/SemiDirectProduct/Strict.hs b/src/Data/Monoid/SemiDirectProduct/Strict.hs -index 2d783a2..bdbc98c 100644 ---- a/src/Data/Monoid/SemiDirectProduct/Strict.hs -+++ b/src/Data/Monoid/SemiDirectProduct/Strict.hs -@@ -12,8 +12,9 @@ module Data.Monoid.SemiDirectProduct.Strict - ) where - - #if !MIN_VERSION_base(4,8,0) --import Data.Monoid -+import Data.Monoid (Monoid(..)) - #endif -+import Data.Semigroup (Semigroup(..)) - - import Data.Monoid.Action - -@@ -33,11 +34,19 @@ data Semi s m = Semi s !m - unSemi :: Semi s m -> (s,m) - unSemi (Semi s m) = (s,m) - -+instance (Semigroup m, Semigroup s, Action m s) => Semigroup (Semi s m) where -+ Semi xs xm <> Semi ys ym = Semi (xs <> (xm `act` ys)) (xm <> ym) -+ {-# INLINE (<>) #-} -+ sconcat = foldr1 (<>) -+ {-# INLINE sconcat #-} -+ - instance (Monoid m, Monoid s, Action m s) => Monoid (Semi s m) where - mempty = Semi mempty mempty - {-# INLINE mempty #-} -+#if !MIN_VERSION_base(4,11,0) - mappend (Semi xs xm) (Semi ys ym) = Semi (xs `mappend` (xm `act` ys)) (xm `mappend` ym) - {-# INLINE mappend #-} -+#endif - mconcat = foldr mappend mempty - {-# INLINE mconcat #-} - diff --git a/patches/multiset-0.3.4.patch b/patches/multiset-0.3.4.patch deleted file mode 100644 index ebbe586195f22cecbf8c7a97125f530dea8c7205..0000000000000000000000000000000000000000 --- a/patches/multiset-0.3.4.patch +++ /dev/null @@ -1,37 +0,0 @@ -diff -ru multiset-0.3.4.orig/Data/IntMultiSet.hs multiset-0.3.4/Data/IntMultiSet.hs ---- multiset-0.3.4.orig/Data/IntMultiSet.hs 2018-05-28 16:34:34.000000000 -0400 -+++ multiset-0.3.4/Data/IntMultiSet.hs 2018-07-09 11:14:01.674267583 -0400 -@@ -146,6 +146,7 @@ - import Data.IntSet (IntSet) - import Data.MultiSet (MultiSet) - import qualified Data.IntMap.Strict as Map -+import qualified Data.IntMap.Internal.Debug as MapDebug - import qualified Data.IntSet as Set - import qualified Data.List as List - import qualified Data.MultiSet as MultiSet -@@ -771,4 +772,4 @@ - - -} - showTreeWith :: Bool -> Bool -> IntMultiSet -> String --showTreeWith hang wide = Map.showTreeWith hang wide . unMS -+showTreeWith hang wide = MapDebug.showTreeWith hang wide . unMS -diff -ru multiset-0.3.4.orig/Data/MultiSet.hs multiset-0.3.4/Data/MultiSet.hs ---- multiset-0.3.4.orig/Data/MultiSet.hs 2018-05-28 16:34:34.000000000 -0400 -+++ multiset-0.3.4/Data/MultiSet.hs 2018-07-09 11:13:33.618266876 -0400 -@@ -152,6 +152,7 @@ - import Data.Map.Strict (Map) - import Data.Set (Set) - import qualified Data.Map.Strict as Map -+import qualified Data.Map.Internal.Debug as MapDebug - import qualified Data.Set as Set - import qualified Data.List as List - import Control.DeepSeq (NFData(..)) -@@ -762,7 +763,7 @@ - - -} - showTreeWith :: Show a => Bool -> Bool -> MultiSet a -> String --showTreeWith hang wide = Map.showTreeWith s hang wide . unMS -+showTreeWith hang wide = MapDebug.showTreeWith s hang wide . unMS - where s a n = showChar '(' . shows n . showString "*)" . shows a $ "" - - {-------------------------------------------------------------------- diff --git a/patches/nanospec-0.2.1.patch b/patches/nanospec-0.2.1.patch deleted file mode 100644 index 6d77aa8fda94f186ced82297131d518f9855810d..0000000000000000000000000000000000000000 --- a/patches/nanospec-0.2.1.patch +++ /dev/null @@ -1,14 +0,0 @@ -diff --git a/src/Test/Hspec.hs b/src/Test/Hspec.hs -index de284c5..77f7b26 100644 ---- a/src/Test/Hspec.hs -+++ b/src/Test/Hspec.hs -@@ -75,6 +75,9 @@ it label = add . SpecExample label . evaluateExpectation - -- | Summary of a test run. - data Summary = Summary Int Int - -+instance Semigroup Summary where -+ (<>) = mappend -+ - instance Monoid Summary where - mempty = Summary 0 0 - (Summary x1 x2) `mappend` (Summary y1 y2) = Summary (x1 + y1) (x2 + y2) diff --git a/patches/non-negative-0.1.1.2.patch b/patches/non-negative-0.1.1.2.patch deleted file mode 100644 index 408c338ce3d100aafd47c001c6cc3972f0c2f1d7..0000000000000000000000000000000000000000 --- a/patches/non-negative-0.1.1.2.patch +++ /dev/null @@ -1,58 +0,0 @@ -diff -ru non-negative-0.1.1.2.orig/src/Numeric/NonNegative/ChunkyPrivate.hs non-negative-0.1.1.2/src/Numeric/NonNegative/ChunkyPrivate.hs ---- non-negative-0.1.1.2.orig/src/Numeric/NonNegative/ChunkyPrivate.hs 2017-07-31 05:26:02.000000000 -0400 -+++ non-negative-0.1.1.2/src/Numeric/NonNegative/ChunkyPrivate.hs 2018-01-24 11:57:00.559457730 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {- | - Copyright : (c) Henning Thielemann 2008-2010 - -@@ -21,6 +22,9 @@ - import Data.Tuple.HT (mapSnd, ) - - import qualified Data.Monoid as Mn -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - import Test.QuickCheck (Arbitrary(arbitrary, shrink)) - - {- | -@@ -192,6 +196,10 @@ - (cs,rm) = recourse (toChunks x0) 0 - in (fromChunks cs, rm) - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup (T a) where -+ (<>) = lift2 (++) -+#endif - - instance Mn.Monoid (T a) where - mempty = zero -diff -ru non-negative-0.1.1.2.orig/src/Numeric/NonNegative/Wrapper.hs non-negative-0.1.1.2/src/Numeric/NonNegative/Wrapper.hs ---- non-negative-0.1.1.2.orig/src/Numeric/NonNegative/Wrapper.hs 2017-07-31 05:26:02.000000000 -0400 -+++ non-negative-0.1.1.2/src/Numeric/NonNegative/Wrapper.hs 2018-01-24 11:58:03.951459326 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {- | - Copyright : (c) Henning Thielemann 2007-2010 - -@@ -17,6 +18,9 @@ - import qualified Numeric.NonNegative.Class as NonNeg - import Data.Monoid (Monoid, ) - import qualified Data.Monoid as Monoid -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - - import Test.QuickCheck (Arbitrary(arbitrary, shrink)) - import Data.Tuple.HT (mapPair, mapSnd, ) -@@ -104,6 +108,10 @@ - lift2 :: (a -> a -> a) -> (T a -> T a -> T a) - lift2 f (Cons x) (Cons y) = Cons $ f x y - -+#if MIN_VERSION_base(4,9,0) -+instance (Num a) => Semigroup (T a) where -+ Cons x <> Cons y = Cons (x+y) -+#endif - - instance (Num a) => Monoid (T a) where - mempty = Cons 0 diff --git a/patches/numeric-prelude-0.4.2.patch b/patches/numeric-prelude-0.4.2.patch deleted file mode 100644 index 896f05ed113b4cb55fdda4904f5a9be78edce5d1..0000000000000000000000000000000000000000 --- a/patches/numeric-prelude-0.4.2.patch +++ /dev/null @@ -1,30 +0,0 @@ -diff -ru numeric-prelude-0.4.2.orig/src/Number/NonNegativeChunky.hs numeric-prelude-0.4.2/src/Number/NonNegativeChunky.hs ---- numeric-prelude-0.4.2.orig/src/Number/NonNegativeChunky.hs 2015-04-04 16:05:37.000000000 -0400 -+++ numeric-prelude-0.4.2/src/Number/NonNegativeChunky.hs 2018-01-24 12:07:02.131472879 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {- | - Copyright : (c) Henning Thielemann 2007-2010 - -@@ -35,6 +36,9 @@ - - import qualified Algebra.Monoid as Monoid - import qualified Data.Monoid as Mn98 -+#if MIN_VERSION_base(4,9,0) -+import qualified Data.Semigroup as Semigroup -+#endif - - import Control.Monad (liftM, liftM2, ) - import Data.Tuple.HT (mapFst, mapSnd, mapPair, ) -@@ -324,6 +328,11 @@ - fromRational = fromNumber_ . P98.fromRational - (/) = notImplemented "(/)" - -+#if MIN_VERSION_base(4,9,0) -+instance (NonNeg.C a) => Semigroup.Semigroup (T a) where -+ (<>) = (Monoid.<*>) -+#endif -+ - instance (NonNeg.C a) => Mn98.Monoid (T a) where - mempty = Monoid.idt - mappend = (Monoid.<*>) diff --git a/patches/numtype-dk-0.5.0.1.patch b/patches/numtype-dk-0.5.0.1.patch deleted file mode 100644 index 2049d817857a8f41fd7cfca36133978ba2592dd4..0000000000000000000000000000000000000000 --- a/patches/numtype-dk-0.5.0.1.patch +++ /dev/null @@ -1,48 +0,0 @@ -diff -ru numtype-dk-0.5.0.1.orig/Numeric/NumType/DK/Integers.hs numtype-dk-0.5.0.1/Numeric/NumType/DK/Integers.hs ---- numtype-dk-0.5.0.1.orig/Numeric/NumType/DK/Integers.hs 2016-05-16 09:14:04.000000000 -0400 -+++ numtype-dk-0.5.0.1/Numeric/NumType/DK/Integers.hs 2018-07-04 21:27:12.448314861 -0400 -@@ -7,6 +7,9 @@ - {-# LANGUAGE TypeFamilies #-} - {-# LANGUAGE TypeOperators #-} - {-# LANGUAGE UndecidableInstances #-} -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - - {- | - Copyright : Copyright (C) 2006-2015 Bjorn Buckwalter -@@ -20,7 +23,7 @@ - - Type-level integers for GHC 7.8+. - --We provide type level arithmetic operations. We also provide term-level arithmetic operations on proxys, -+We provide type level arithmetic operations. We also provide term-level arithmetic operations on proxys, - and conversion from the type level to the term level. - - = Planned Obsolesence -@@ -268,7 +271,7 @@ - -- | TypeInt division. - type family (i::TypeInt) / (i'::TypeInt) :: TypeInt - where -- -+ - i / 'Pos1 = i - i / 'Neg1 = Negate i - -- @Zero / n = Zero@ would allow division by zero. -diff -ru numtype-dk-0.5.0.1.orig/Numeric/NumType/DK/Naturals.hs numtype-dk-0.5.0.1/Numeric/NumType/DK/Naturals.hs ---- numtype-dk-0.5.0.1.orig/Numeric/NumType/DK/Naturals.hs 2015-05-11 09:10:15.000000000 -0400 -+++ numtype-dk-0.5.0.1/Numeric/NumType/DK/Naturals.hs 2018-07-04 21:27:41.472315592 -0400 -@@ -1,9 +1,13 @@ - {-# LANGUAGE AutoDeriveTypeable #-} -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DataKinds #-} - {-# LANGUAGE FlexibleInstances #-} - {-# LANGUAGE TypeFamilies #-} - {-# LANGUAGE TypeOperators #-} - {-# LANGUAGE UndecidableInstances #-} -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - - module Numeric.NumType.DK.Naturals where - diff --git a/patches/optional-args-1.0.1.patch b/patches/optional-args-1.0.1.patch deleted file mode 100644 index a00c8006a298f80c311ea61f79e73389c53fbb0e..0000000000000000000000000000000000000000 --- a/patches/optional-args-1.0.1.patch +++ /dev/null @@ -1,28 +0,0 @@ -diff -ru optional-args-1.0.1.orig/src/Data/Optional.hs optional-args-1.0.1/src/Data/Optional.hs ---- optional-args-1.0.1.orig/src/Data/Optional.hs 2016-04-16 06:11:21.000000000 +0200 -+++ optional-args-1.0.1/src/Data/Optional.hs 2017-09-14 22:38:35.114394135 +0200 -@@ -97,6 +97,7 @@ - import Data.Foldable (Foldable) - import Data.Traversable (Traversable) - import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.String (IsString(..)) - - -- | A function argument that has a `Default` value -@@ -125,10 +126,13 @@ - mzero = empty - mplus = (<|>) - -+-- TODO: can be more general but needs CPP -+instance Monoid a => Semigroup (Optional a) where -+ (<>) = liftA2 mappend -+ - instance Monoid a => Monoid (Optional a) where - mempty = pure mempty -- -- mappend = liftA2 mappend -+ mappend = (<>) - - instance IsString a => IsString (Optional a) where - fromString str = pure (fromString str) -Only in optional-args-1.0.1/src/Data: Optional.hs~ diff --git a/patches/pandoc-1.19.2.4.patch b/patches/pandoc-1.19.2.4.patch deleted file mode 100644 index 8f632305e6ab6afc253365f1c4a47a6de8531526..0000000000000000000000000000000000000000 --- a/patches/pandoc-1.19.2.4.patch +++ /dev/null @@ -1,170 +0,0 @@ -diff -ru pandoc-1.19.2.4.orig/src/Text/Pandoc/MediaBag.hs pandoc-1.19.2.4/src/Text/Pandoc/MediaBag.hs ---- pandoc-1.19.2.4.orig/src/Text/Pandoc/MediaBag.hs 2017-09-10 15:38:42.000000000 +0200 -+++ pandoc-1.19.2.4/src/Text/Pandoc/MediaBag.hs 2017-09-18 12:33:20.629769757 +0200 -@@ -48,13 +48,14 @@ - import System.IO (stderr) - import Data.Data (Data) - import Data.Typeable (Typeable) -+import Data.Semigroup (Semigroup(..)) - - -- | A container for a collection of binary resources, with names and - -- mime types. Note that a 'MediaBag' is a Monoid, so 'mempty' - -- can be used for an empty 'MediaBag', and '<>' can be used to append - -- two 'MediaBag's. - newtype MediaBag = MediaBag (M.Map [String] (MimeType, BL.ByteString)) -- deriving (Monoid, Data, Typeable) -+ deriving (Semigroup, Monoid, Data, Typeable) - - instance Show MediaBag where - show bag = "MediaBag " ++ show (mediaDirectory bag) -Only in pandoc-1.19.2.4/src/Text/Pandoc: MediaBag.hs~ -diff -ru pandoc-1.19.2.4.orig/src/Text/Pandoc/Parsing.hs pandoc-1.19.2.4/src/Text/Pandoc/Parsing.hs ---- pandoc-1.19.2.4.orig/src/Text/Pandoc/Parsing.hs 2017-09-10 15:38:42.000000000 +0200 -+++ pandoc-1.19.2.4/src/Text/Pandoc/Parsing.hs 2017-09-18 12:35:29.149053810 +0200 -@@ -192,6 +192,7 @@ - import Control.Monad.Reader - import Control.Monad.Identity - import Data.Maybe (catMaybes) -+import Data.Semigroup (Semigroup(..)) - - import Text.Pandoc.Error - -@@ -210,9 +211,12 @@ - asksF :: (ParserState -> a) -> F a - asksF f = F $ asks f - -+instance Monoid a => Semigroup (F a) where -+ (<>) = liftM2 mappend -+ - instance Monoid a => Monoid (F a) where - mempty = return mempty -- mappend = liftM2 mappend -+ mappend = (<>) - mconcat = liftM mconcat . sequence - - -- | Parse any line of text -Only in pandoc-1.19.2.4/src/Text/Pandoc: Parsing.hs~ -diff -ru pandoc-1.19.2.4.orig/src/Text/Pandoc/Pretty.hs pandoc-1.19.2.4/src/Text/Pandoc/Pretty.hs ---- pandoc-1.19.2.4.orig/src/Text/Pandoc/Pretty.hs 2017-09-10 15:38:42.000000000 +0200 -+++ pandoc-1.19.2.4/src/Text/Pandoc/Pretty.hs 2017-09-18 12:30:23.334768812 +0200 -@@ -83,7 +83,7 @@ - import Data.String - import Control.Monad.State - import Data.Char (isSpace) --import Data.Monoid ((<>)) -+import Data.Semigroup (Semigroup(..)) - - data RenderState a = RenderState{ - output :: [a] -- ^ In reverse order -@@ -109,7 +109,7 @@ - deriving (Show) - - newtype Doc = Doc { unDoc :: Seq D } -- deriving (Monoid, Show) -+ deriving (Semigroup, Monoid, Show) - - instance IsString Doc where - fromString = text -Only in pandoc-1.19.2.4/src/Text/Pandoc: Pretty.hs~ -diff -ru pandoc-1.19.2.4.orig/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs pandoc-1.19.2.4/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs ---- pandoc-1.19.2.4.orig/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs 2017-09-10 15:38:42.000000000 +0200 -+++ pandoc-1.19.2.4/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs 2017-09-18 12:31:56.530242510 +0200 -@@ -268,9 +268,12 @@ - newtype ParallelArrow a b c = CoEval { evalParallelArrow :: a b c } - deriving (Eq, Ord, Show) - -+instance (Arrow a, Monoid m) => Semigroup (ParallelArrow a b m) where -+ (CoEval a) <> (CoEval ~b) = CoEval $ a &&& b >>% mappend -+ - instance (Arrow a, Monoid m) => Monoid (ParallelArrow a b m) where - mempty = CoEval $ returnV mempty -- (CoEval a) `mappend` (CoEval ~b) = CoEval $ a &&& b >>% mappend -+ mappend = (<>) - - -- | Evaluates a collection of arrows in a parallel fashion. - -- -@@ -301,14 +304,18 @@ - - - instance (ArrowChoice a, Monoid failure) -- => Monoid (AlternativeArrow a input failure success) where -- mempty = TryArrow $ returnV $ Left mempty -- (TryArrow a) `mappend` (TryArrow b) -+ => Semigroup (AlternativeArrow a input failure success) where -+ (TryArrow a) <> (TryArrow b) - = TryArrow $ a &&& b - >>^ \(a',~b') - -> ( (\a'' -> left (mappend a'') b') ||| Right ) - a' - -+instance (ArrowChoice a, Monoid failure) -+ => Monoid (AlternativeArrow a input failure success) where -+ mempty = TryArrow $ returnV $ Left mempty -+ mappend = (<>) -+ - -- | Evaluates a collection of fallible arrows, trying each one in succession. - -- Left values are interpreted as failures, right values as successes. - -- -Only in pandoc-1.19.2.4/src/Text/Pandoc/Readers/Odt/Arrows: Utils.hs~ -diff -ru pandoc-1.19.2.4.orig/src/Text/Pandoc/Readers/Odt/StyleReader.hs pandoc-1.19.2.4/src/Text/Pandoc/Readers/Odt/StyleReader.hs ---- pandoc-1.19.2.4.orig/src/Text/Pandoc/Readers/Odt/StyleReader.hs 2017-09-10 15:38:42.000000000 +0200 -+++ pandoc-1.19.2.4/src/Text/Pandoc/Readers/Odt/StyleReader.hs 2017-09-18 12:33:00.137883841 +0200 -@@ -80,6 +80,7 @@ - import Data.Default - import Data.List ( unfoldr ) - import Data.Maybe -+import Data.Semigroup (Semigroup(..)) - - import qualified Text.XML.Light as XML - -@@ -197,15 +198,18 @@ - } - deriving ( Show ) - ---- Styles from a monoid under union --instance Monoid Styles where -- mempty = Styles M.empty M.empty M.empty -- mappend (Styles sBn1 dSm1 lsBn1) -- (Styles sBn2 dSm2 lsBn2) -+instance Semigroup Styles where -+ (Styles sBn1 dSm1 lsBn1) <> (Styles sBn2 dSm2 lsBn2) - = Styles (M.union sBn1 sBn2) - (M.union dSm1 dSm2) - (M.union lsBn1 lsBn2) - -+ -+-- Styles from a monoid under union -+instance Monoid Styles where -+ mempty = Styles M.empty M.empty M.empty -+ mappend = (<>) -+ - -- Not all families from the specifications are implemented, only those we need. - -- But there are none that are not mentioned here. - data StyleFamily = FaText | FaParagraph -Only in pandoc-1.19.2.4/src/Text/Pandoc/Readers/Odt: StyleReader.hs~ -diff -ru pandoc-1.19.2.4.orig/src/Text/Pandoc/Readers/Org/ParserState.hs pandoc-1.19.2.4/src/Text/Pandoc/Readers/Org/ParserState.hs ---- pandoc-1.19.2.4.orig/src/Text/Pandoc/Readers/Org/ParserState.hs 2017-09-10 15:38:42.000000000 +0200 -+++ pandoc-1.19.2.4/src/Text/Pandoc/Readers/Org/ParserState.hs 2017-09-18 12:38:03.808191278 +0200 -@@ -56,6 +56,7 @@ - import Data.Default (Default(..)) - import qualified Data.Map as M - import qualified Data.Set as Set -+import Data.Semigroup (Semigroup(..)) - - import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines ) - import Text.Pandoc.Definition ( Meta(..), nullMeta ) -@@ -238,9 +239,12 @@ - newtype F a = F { unF :: Reader OrgParserState a - } deriving (Functor, Applicative, Monad) - -+instance Monoid a => Semigroup (F a) where -+ (<>) = liftM2 mappend -+ - instance Monoid a => Monoid (F a) where - mempty = return mempty -- mappend = liftM2 mappend -+ mappend = (<>) - mconcat = fmap mconcat . sequence - - runF :: F a -> OrgParserState -> a -Only in pandoc-1.19.2.4/src/Text/Pandoc/Readers/Org: ParserState.hs~ diff --git a/patches/pandoc-types-1.17.0.5.patch b/patches/pandoc-types-1.17.0.5.patch deleted file mode 100644 index f2fe4b5ca38e5c4f741bef7f51178d416c2bd44b..0000000000000000000000000000000000000000 --- a/patches/pandoc-types-1.17.0.5.patch +++ /dev/null @@ -1,84 +0,0 @@ -diff -ru pandoc-types-1.17.1.orig/Text/Pandoc/Builder.hs pandoc-types-1.17.1/Text/Pandoc/Builder.hs ---- pandoc-types-1.17.1.orig/Text/Pandoc/Builder.hs 2017-08-20 21:07:01.000000000 +0200 -+++ pandoc-types-1.17.1/Text/Pandoc/Builder.hs 2017-09-18 12:13:20.756536003 +0200 -@@ -177,17 +177,7 @@ - import Data.Data - import Control.Arrow ((***)) - import GHC.Generics (Generic) -- --#if MIN_VERSION_base(4,5,0) ---- (<>) is defined in Data.Monoid --#else --infixr 6 <> -- ---- | An infix synonym for 'mappend'. --(<>) :: Monoid m => m -> m -> m --(<>) = mappend --{-# INLINE (<>) #-} --#endif -+import Data.Semigroup (Semigroup(..)) - - newtype Many a = Many { unMany :: Seq a } - deriving (Data, Ord, Eq, Typeable, Foldable, Traversable, Functor, Show, Read) -@@ -209,11 +199,15 @@ - type Inlines = Many Inline - type Blocks = Many Block - -+deriving instance Semigroup Blocks - deriving instance Monoid Blocks - - instance Monoid Inlines where - mempty = Many mempty -- (Many xs) `mappend` (Many ys) = -+ mappend = (<>) -+ -+instance Semigroup Inlines where -+ (Many xs) <> (Many ys) = - case (viewr xs, viewl ys) of - (EmptyR, _) -> Many ys - (_, EmptyL) -> Many xs -Only in pandoc-types-1.17.1/Text/Pandoc: Builder.hs~ -diff -ru pandoc-types-1.17.1.orig/Text/Pandoc/Definition.hs pandoc-types-1.17.1/Text/Pandoc/Definition.hs ---- pandoc-types-1.17.1.orig/Text/Pandoc/Definition.hs 2017-08-20 21:07:01.000000000 +0200 -+++ pandoc-types-1.17.1/Text/Pandoc/Definition.hs 2017-09-18 12:11:07.829292907 +0200 -@@ -88,27 +88,34 @@ - import Control.Applicative ((<$>), (<*>)) - import Control.DeepSeq.Generics - #endif -+import Data.Semigroup (Semigroup(..)) - import Paths_pandoc_types (version) - import Data.Version (Version, versionBranch) - - data Pandoc = Pandoc Meta [Block] - deriving (Eq, Ord, Read, Show, Typeable, Data, Generic) - -+instance Semigroup Pandoc where -+ (Pandoc m1 bs1) <> (Pandoc m2 bs2) = -+ Pandoc (m1 <> m2) (bs1 <> bs2) -+ - instance Monoid Pandoc where - mempty = Pandoc mempty mempty -- (Pandoc m1 bs1) `mappend` (Pandoc m2 bs2) = -- Pandoc (m1 `mappend` m2) (bs1 `mappend` bs2) -+ mappend = (<>) - - -- | Metadata for the document: title, authors, date. - newtype Meta = Meta { unMeta :: M.Map String MetaValue } - deriving (Eq, Ord, Show, Read, Typeable, Data, Generic) - --instance Monoid Meta where -- mempty = Meta (M.empty) -- (Meta m1) `mappend` (Meta m2) = Meta (M.union m1 m2) -+instance Semigroup Meta where -+ (Meta m1) <> (Meta m2) = Meta (M.union m1 m2) - -- note: M.union is left-biased, so if there are fields in both m1 - -- and m2, m1 wins. - -+instance Monoid Meta where -+ mempty = Meta (M.empty) -+ mappend = (<>) -+ - data MetaValue = MetaMap (M.Map String MetaValue) - | MetaList [MetaValue] - | MetaBool Bool -Only in pandoc-types-1.17.1/Text/Pandoc: Definition.hs~ diff --git a/patches/pandoc-types-1.17.1.patch b/patches/pandoc-types-1.17.1.patch deleted file mode 100644 index f2fe4b5ca38e5c4f741bef7f51178d416c2bd44b..0000000000000000000000000000000000000000 --- a/patches/pandoc-types-1.17.1.patch +++ /dev/null @@ -1,84 +0,0 @@ -diff -ru pandoc-types-1.17.1.orig/Text/Pandoc/Builder.hs pandoc-types-1.17.1/Text/Pandoc/Builder.hs ---- pandoc-types-1.17.1.orig/Text/Pandoc/Builder.hs 2017-08-20 21:07:01.000000000 +0200 -+++ pandoc-types-1.17.1/Text/Pandoc/Builder.hs 2017-09-18 12:13:20.756536003 +0200 -@@ -177,17 +177,7 @@ - import Data.Data - import Control.Arrow ((***)) - import GHC.Generics (Generic) -- --#if MIN_VERSION_base(4,5,0) ---- (<>) is defined in Data.Monoid --#else --infixr 6 <> -- ---- | An infix synonym for 'mappend'. --(<>) :: Monoid m => m -> m -> m --(<>) = mappend --{-# INLINE (<>) #-} --#endif -+import Data.Semigroup (Semigroup(..)) - - newtype Many a = Many { unMany :: Seq a } - deriving (Data, Ord, Eq, Typeable, Foldable, Traversable, Functor, Show, Read) -@@ -209,11 +199,15 @@ - type Inlines = Many Inline - type Blocks = Many Block - -+deriving instance Semigroup Blocks - deriving instance Monoid Blocks - - instance Monoid Inlines where - mempty = Many mempty -- (Many xs) `mappend` (Many ys) = -+ mappend = (<>) -+ -+instance Semigroup Inlines where -+ (Many xs) <> (Many ys) = - case (viewr xs, viewl ys) of - (EmptyR, _) -> Many ys - (_, EmptyL) -> Many xs -Only in pandoc-types-1.17.1/Text/Pandoc: Builder.hs~ -diff -ru pandoc-types-1.17.1.orig/Text/Pandoc/Definition.hs pandoc-types-1.17.1/Text/Pandoc/Definition.hs ---- pandoc-types-1.17.1.orig/Text/Pandoc/Definition.hs 2017-08-20 21:07:01.000000000 +0200 -+++ pandoc-types-1.17.1/Text/Pandoc/Definition.hs 2017-09-18 12:11:07.829292907 +0200 -@@ -88,27 +88,34 @@ - import Control.Applicative ((<$>), (<*>)) - import Control.DeepSeq.Generics - #endif -+import Data.Semigroup (Semigroup(..)) - import Paths_pandoc_types (version) - import Data.Version (Version, versionBranch) - - data Pandoc = Pandoc Meta [Block] - deriving (Eq, Ord, Read, Show, Typeable, Data, Generic) - -+instance Semigroup Pandoc where -+ (Pandoc m1 bs1) <> (Pandoc m2 bs2) = -+ Pandoc (m1 <> m2) (bs1 <> bs2) -+ - instance Monoid Pandoc where - mempty = Pandoc mempty mempty -- (Pandoc m1 bs1) `mappend` (Pandoc m2 bs2) = -- Pandoc (m1 `mappend` m2) (bs1 `mappend` bs2) -+ mappend = (<>) - - -- | Metadata for the document: title, authors, date. - newtype Meta = Meta { unMeta :: M.Map String MetaValue } - deriving (Eq, Ord, Show, Read, Typeable, Data, Generic) - --instance Monoid Meta where -- mempty = Meta (M.empty) -- (Meta m1) `mappend` (Meta m2) = Meta (M.union m1 m2) -+instance Semigroup Meta where -+ (Meta m1) <> (Meta m2) = Meta (M.union m1 m2) - -- note: M.union is left-biased, so if there are fields in both m1 - -- and m2, m1 wins. - -+instance Monoid Meta where -+ mempty = Meta (M.empty) -+ mappend = (<>) -+ - data MetaValue = MetaMap (M.Map String MetaValue) - | MetaList [MetaValue] - | MetaBool Bool -Only in pandoc-types-1.17.1/Text/Pandoc: Definition.hs~ diff --git a/patches/patience-0.1.1.patch b/patches/patience-0.1.1.patch deleted file mode 100644 index e844e1d9df5e1c2bb9cd8121d71df3521de0a11d..0000000000000000000000000000000000000000 --- a/patches/patience-0.1.1.patch +++ /dev/null @@ -1,20 +0,0 @@ -diff -ru patience-0.1.1/Data/Algorithm/Patience.hs patience-modified/Data/Algorithm/Patience.hs ---- patience-0.1.1/Data/Algorithm/Patience.hs 2011-08-17 08:08:14.000000000 +0800 -+++ patience-modified/Data/Algorithm/Patience.hs 2018-07-11 15:17:45.021338649 +0800 -@@ -15,6 +15,7 @@ - import Data.Sequence ( (<|), (|>), (><), ViewL(..), ViewR(..) ) - import qualified Data.Foldable as F - import qualified Data.Map as M -+import qualified Data.Map.Strict as MS - import qualified Data.IntMap as IM - - import Data.List -@@ -68,7 +69,7 @@ - -- Elements whose second component appears exactly once. - unique :: (Ord t) => S.Seq (a,t) -> M.Map t a - unique = M.mapMaybe id . F.foldr ins M.empty where -- ins (a,x) = M.insertWith' (\_ _ -> Nothing) x (Just a) -+ ins (a,x) = MS.insertWith (\_ _ -> Nothing) x (Just a) - - -- Given two sequences of numbered "lines", returns a list of points - -- where unique lines match up. diff --git a/patches/pipes-concurrency-2.0.8.patch b/patches/pipes-concurrency-2.0.8.patch deleted file mode 100644 index 31940a8f4dc1872dfe36b77f364675438a851707..0000000000000000000000000000000000000000 --- a/patches/pipes-concurrency-2.0.8.patch +++ /dev/null @@ -1,62 +0,0 @@ -diff -ru pipes-concurrency-2.0.8.orig/pipes-concurrency.cabal pipes-concurrency-2.0.8/pipes-concurrency.cabal ---- pipes-concurrency-2.0.8.orig/pipes-concurrency.cabal 2017-09-03 20:26:05.000000000 +0200 -+++ pipes-concurrency-2.0.8/pipes-concurrency.cabal 2017-09-17 11:32:32.531659094 +0200 -@@ -34,6 +34,7 @@ - base >= 4 && < 5 , - async >= 2.0.0.0 && < 2.2, - contravariant >= 1.3.3 && < 1.5, -+ semigroups >= 0.18 && < 0.19, - pipes >= 4.0 && < 4.4, - stm >= 2.4.3 && < 2.5, - void >= 0.6 && < 1 -diff -ru pipes-concurrency-2.0.8.orig/src/Pipes/Concurrent.hs pipes-concurrency-2.0.8/src/Pipes/Concurrent.hs ---- pipes-concurrency-2.0.8.orig/src/Pipes/Concurrent.hs 2017-09-03 20:26:05.000000000 +0200 -+++ pipes-concurrency-2.0.8/src/Pipes/Concurrent.hs 2017-09-17 11:32:32.531659094 +0200 -@@ -1,6 +1,6 @@ - -- | Asynchronous communication between pipes - --{-# LANGUAGE RankNTypes, Safe #-} -+{-# LANGUAGE CPP, RankNTypes, Safe #-} - - module Pipes.Concurrent ( - -- * Inputs and Outputs -@@ -39,6 +39,7 @@ - import Data.Functor.Contravariant.Divisible ( - Divisible(divide, conquer), Decidable(lose, choose)) - import Data.Monoid (Monoid(mempty, mappend)) -+import Data.Semigroup - import Data.Void (absurd) - import Pipes (MonadIO(liftIO), yield, await, Producer', Consumer') - import System.Mem (performGC) -@@ -81,9 +82,14 @@ - mzero = empty - mplus = (<|>) - -+instance Semigroup (Input a) where -+ (<>) = (<|>) -+ - instance Monoid (Input a) where - mempty = empty -- mappend = (<|>) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - {-| An exhaustible sink of values - -@@ -92,9 +98,14 @@ - newtype Output a = Output { - send :: a -> S.STM Bool } - -+instance Semigroup (Output a) where -+ i1 <> i2 = Output (\a -> (||) <$> send i1 a <*> send i2 a) -+ - instance Monoid (Output a) where - mempty = Output (\_ -> return False) -- mappend i1 i2 = Output (\a -> (||) <$> send i1 a <*> send i2 a) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | This instance is useful for creating new tagged address, similar to elm's - -- Signal.forwardTo. In fact elm's forwardTo is just 'flip contramap' diff --git a/patches/polyparse-1.12.patch b/patches/polyparse-1.12.patch deleted file mode 100644 index afa85515aae57cf99cfcff3a434c189eeab2a175..0000000000000000000000000000000000000000 --- a/patches/polyparse-1.12.patch +++ /dev/null @@ -1,302 +0,0 @@ -diff --git a/src/Text/ParserCombinators/HuttonMeijer.hs b/src/Text/ParserCombinators/HuttonMeijer.hs -index 7cb4b75..94a3f17 100644 ---- a/src/Text/ParserCombinators/HuttonMeijer.hs -+++ b/src/Text/ParserCombinators/HuttonMeijer.hs -@@ -37,6 +37,7 @@ module Text.ParserCombinators.HuttonMeijer - import Data.Char - import Control.Applicative ( Applicative(pure,(<*>)), Alternative(empty,(<|>)) ) - import Control.Monad -+import qualified Control.Monad.Fail as Fail - - infixr 5 +++ - -@@ -62,6 +63,9 @@ instance Monad Parser where - -- >>= :: Parser a -> (a -> Parser b) -> Parser b - (P p) >>= f = P (\inp -> concat [papply (f v) out | (v,out) <- p inp]) - -+ fail = Fail.fail -+ -+instance Fail.MonadFail Parser where - -- fail :: String -> Parser a - fail _ = P (\_ -> []) - -diff --git a/src/Text/ParserCombinators/HuttonMeijerWallace.hs b/src/Text/ParserCombinators/HuttonMeijerWallace.hs -index 40cca1a..6d304e6 100644 ---- a/src/Text/ParserCombinators/HuttonMeijerWallace.hs -+++ b/src/Text/ParserCombinators/HuttonMeijerWallace.hs -@@ -56,6 +56,7 @@ module Text.ParserCombinators.HuttonMeijerWallace - import Data.Char - import Control.Applicative ( Applicative(pure,(<*>)), Alternative(empty,(<|>)) ) - import Control.Monad -+import qualified Control.Monad.Fail as Fail - - infixr 5 +++ - -@@ -88,6 +89,9 @@ instance Monad (Parser s t e) where - [ papply' (f v) s out | (v,s,out) <- res ] - Left err -> Left err - ) -+ fail = Fail.fail -+ -+instance Fail.MonadFail (Parser s t e) where - -- fail :: String -> Parser s t e a - fail err = P (\st inp -> Right []) - -- I know it's counterintuitive, but we want no-parse, not an error. -diff --git a/src/Text/ParserCombinators/Poly/ByteString.hs b/src/Text/ParserCombinators/Poly/ByteString.hs -index 28f57b4..aab1a62 100644 ---- a/src/Text/ParserCombinators/Poly/ByteString.hs -+++ b/src/Text/ParserCombinators/Poly/ByteString.hs -@@ -23,6 +23,7 @@ import Text.ParserCombinators.Poly.Result - import qualified Data.ByteString.Lazy as BS - import Data.ByteString.Lazy (ByteString) - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - import Data.Word - - -- | This @Parser@ datatype is a specialised parsing monad with error -@@ -39,13 +40,16 @@ instance Functor Parser where - - instance Monad Parser where - return x = P (\ts-> Success ts x) -- fail e = P (\ts-> Failure ts e) -+ fail = Fail.fail - (P f) >>= g = P (continue . f) - where - continue (Success ts x) = let (P g') = g x in g' ts - continue (Committed r) = Committed (continue r) - continue (Failure ts e) = Failure ts e - -+instance Fail.MonadFail Parser where -+ fail e = P (\ts-> Failure ts e) -+ - instance Commitment Parser where - commit (P p) = P (Committed . squash . p) - where -diff --git a/src/Text/ParserCombinators/Poly/ByteStringChar.hs b/src/Text/ParserCombinators/Poly/ByteStringChar.hs -index 27b238a..162e32a 100644 ---- a/src/Text/ParserCombinators/Poly/ByteStringChar.hs -+++ b/src/Text/ParserCombinators/Poly/ByteStringChar.hs -@@ -23,6 +23,7 @@ import Text.ParserCombinators.Poly.Result - import qualified Data.ByteString.Lazy.Char8 as BS - import Data.ByteString.Lazy.Char8 (ByteString) - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - -- | This @Parser@ datatype is a specialised parsing monad with error - -- reporting. Whereas the standard version can be used for arbitrary -@@ -38,13 +39,16 @@ instance Functor Parser where - - instance Monad Parser where - return x = P (\ts-> Success ts x) -- fail e = P (\ts-> Failure ts e) -+ fail = Fail.fail - (P f) >>= g = P (continue . f) - where - continue (Success ts x) = let (P g') = g x in g' ts - continue (Committed r) = Committed (continue r) - continue (Failure ts e) = Failure ts e - -+instance Fail.MonadFail Parser where -+ fail e = P (\ts-> Failure ts e) -+ - instance Commitment Parser where - commit (P p) = P (Committed . squash . p) - where -diff --git a/src/Text/ParserCombinators/Poly/Lazy.hs b/src/Text/ParserCombinators/Poly/Lazy.hs -index 5bdf712..0e471e9 100644 ---- a/src/Text/ParserCombinators/Poly/Lazy.hs -+++ b/src/Text/ParserCombinators/Poly/Lazy.hs -@@ -22,6 +22,7 @@ import Text.ParserCombinators.Poly.Base - import Text.ParserCombinators.Poly.Result - import qualified Text.ParserCombinators.Poly.Parser as P - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - #if __GLASGOW_HASKELL__ - import Control.Exception hiding (bracket) -@@ -44,8 +45,10 @@ instance Functor (Parser t) where - fmap f (P p) = P (fmap f p) - instance Monad (Parser t) where - return x = P (return x) -- fail e = P (fail e) -+ fail = Fail.fail - (P f) >>= g = P (f >>= (\(P g')->g') . g) -+instance Fail.MonadFail (Parser t) where -+ fail e = P (fail e) - instance Commitment (Parser t) where - commit (P p) = P (commit p) - (P p) `adjustErr` f = P (p `adjustErr` f) -diff --git a/src/Text/ParserCombinators/Poly/Lex.hs b/src/Text/ParserCombinators/Poly/Lex.hs -index 65e237d..4f52694 100644 ---- a/src/Text/ParserCombinators/Poly/Lex.hs -+++ b/src/Text/ParserCombinators/Poly/Lex.hs -@@ -30,6 +30,7 @@ module Text.ParserCombinators.Poly.Lex - import Text.ParserCombinators.Poly.Base - import Text.ParserCombinators.Poly.Result - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - -- | In a strict language, where creating the entire input list of tokens - -- in one shot may be infeasible, we can use a lazy "callback" kind of -@@ -55,13 +56,16 @@ instance Functor (Parser t) where - - instance Monad (Parser t) where - return x = P (\ts-> Success ts x) -- fail e = P (\ts-> Failure ts e) -+ fail = Fail.fail - (P f) >>= g = P (continue . f) - where - continue (Success ts x) = let (P g') = g x in g' ts - continue (Committed r) = Committed (continue r) - continue (Failure ts e) = Failure ts e - -+instance Fail.MonadFail (Parser t) where -+ fail e = P (\ts-> Failure ts e) -+ - instance Commitment (Parser t) where - commit (P p) = P (Committed . squash . p) - where -diff --git a/src/Text/ParserCombinators/Poly/Parser.hs b/src/Text/ParserCombinators/Poly/Parser.hs -index 66a320c..a453db0 100644 ---- a/src/Text/ParserCombinators/Poly/Parser.hs -+++ b/src/Text/ParserCombinators/Poly/Parser.hs -@@ -20,6 +20,7 @@ module Text.ParserCombinators.Poly.Parser - import Text.ParserCombinators.Poly.Base - import Text.ParserCombinators.Poly.Result - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - -- | This @Parser@ datatype is a fairly generic parsing monad with error - -- reporting. It can be used for arbitrary token types, not just -@@ -39,13 +40,16 @@ instance Applicative (Parser t) where - - instance Monad (Parser t) where - return x = P (\ts-> Success ts x) -- fail e = P (\ts-> Failure ts e) -+ fail = Fail.fail - (P f) >>= g = P (continue . f) - where - continue (Success ts x) = let (P g') = g x in g' ts - continue (Committed r) = Committed (continue r) - continue (Failure ts e) = Failure ts e - -+instance Fail.MonadFail (Parser t) where -+ fail e = P (\ts-> Failure ts e) -+ - instance Alternative (Parser t) where - empty = fail "no parse" - p <|> q = p `onFail` q -diff --git a/src/Text/ParserCombinators/Poly/StateLazy.hs b/src/Text/ParserCombinators/Poly/StateLazy.hs -index 1714d17..f1d3a1a 100644 ---- a/src/Text/ParserCombinators/Poly/StateLazy.hs -+++ b/src/Text/ParserCombinators/Poly/StateLazy.hs -@@ -26,6 +26,7 @@ import Text.ParserCombinators.Poly.Base hiding (manyFinally) - import Text.ParserCombinators.Poly.Result - import qualified Text.ParserCombinators.Poly.StateParser as P - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - #if __GLASGOW_HASKELL__ - import Control.Exception hiding (bracket) -@@ -48,8 +49,10 @@ instance Functor (Parser s t) where - fmap f (P p) = P (fmap f p) - instance Monad (Parser s t) where - return x = P (return x) -- fail e = P (fail e) -+ fail = Fail.fail - (P f) >>= g = P (f >>= (\(P g')->g') . g) -+instance Fail.MonadFail (Parser s t) where -+ fail e = P (fail e) - instance Commitment (Parser s t) where - commit (P p) = P (commit p) - (P p) `adjustErr` f = P (p `adjustErr` f) -diff --git a/src/Text/ParserCombinators/Poly/StateParser.hs b/src/Text/ParserCombinators/Poly/StateParser.hs -index f21ee0a..05236bc 100644 ---- a/src/Text/ParserCombinators/Poly/StateParser.hs -+++ b/src/Text/ParserCombinators/Poly/StateParser.hs -@@ -23,6 +23,7 @@ module Text.ParserCombinators.Poly.StateParser - import Text.ParserCombinators.Poly.Base - import Text.ParserCombinators.Poly.Result - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - -- | This @Parser@ datatype is a fairly generic parsing monad with error - -- reporting, and running state. -@@ -42,13 +43,16 @@ instance Applicative (Parser s t) where - - instance Monad (Parser s t) where - return x = P (\s ts-> Success (ts,s) x) -- fail e = P (\s ts-> Failure (ts,s) e) -+ fail = Fail.fail - (P f) >>= g = P (\s-> continue . f s) - where - continue (Success (ts,s) x) = let (P g') = g x in g' s ts - continue (Committed r) = Committed (continue r) - continue (Failure tss e) = Failure tss e - -+instance Fail.MonadFail (Parser s t) where -+ fail e = P (\s ts-> Failure (ts,s) e) -+ - instance Alternative (Parser s t) where - empty = fail "no parse" - p <|> q = p `onFail` q -diff --git a/src/Text/ParserCombinators/Poly/StateText.hs b/src/Text/ParserCombinators/Poly/StateText.hs -index 1823890..97b576f 100644 ---- a/src/Text/ParserCombinators/Poly/StateText.hs -+++ b/src/Text/ParserCombinators/Poly/StateText.hs -@@ -28,6 +28,7 @@ import Text.ParserCombinators.Poly.Result - import qualified Data.Text.Lazy as T - import Data.Text.Lazy (Text) - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - -- | This @Parser@ datatype is a specialised parsing monad with error - -- reporting. Whereas the standard version can be used for arbitrary -@@ -45,13 +46,16 @@ instance Functor (Parser s) where - - instance Monad (Parser s) where - return x = P (\s ts-> Success (ts,s) x) -- fail e = P (\s ts-> Failure (ts,s) e) -+ fail = Fail.fail - (P f) >>= g = P (\s-> continue . f s) - where - continue (Success (ts,s) x) = let (P g') = g x in g' s ts - continue (Committed r) = Committed (continue r) - continue (Failure ts e) = Failure ts e - -+instance Fail.MonadFail (Parser s) where -+ fail e = P (\s ts-> Failure (ts,s) e) -+ - instance Commitment (Parser s) where - commit (P p) = P (\s-> Committed . squash . p s) - where -diff --git a/src/Text/ParserCombinators/Poly/Text.hs b/src/Text/ParserCombinators/Poly/Text.hs -index 2708e88..44e9ae5 100644 ---- a/src/Text/ParserCombinators/Poly/Text.hs -+++ b/src/Text/ParserCombinators/Poly/Text.hs -@@ -24,6 +24,7 @@ import Text.ParserCombinators.Poly.Result - import qualified Data.Text.Lazy as T - import Data.Text.Lazy (Text) - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - - -- | This @Parser@ datatype is a specialised parsing monad with error - -- reporting. Whereas the standard version can be used for arbitrary -@@ -39,13 +40,16 @@ instance Functor Parser where - - instance Monad Parser where - return x = P (\ts-> Success ts x) -- fail e = P (\ts-> Failure ts e) -+ fail = Fail.fail - (P f) >>= g = P (continue . f) - where - continue (Success ts x) = let (P g') = g x in g' ts - continue (Committed r) = Committed (continue r) - continue (Failure ts e) = Failure ts e - -+instance Fail.MonadFail Parser where -+ fail e = P (\ts-> Failure ts e) -+ - instance Commitment Parser where - commit (P p) = P (Committed . squash . p) - where diff --git a/patches/postgresql-simple-0.5.3.0.patch b/patches/postgresql-simple-0.5.3.0.patch deleted file mode 100644 index bdaec908f05a121cedeeea3ae2995d7806af5d91..0000000000000000000000000000000000000000 --- a/patches/postgresql-simple-0.5.3.0.patch +++ /dev/null @@ -1,93 +0,0 @@ -diff -ru postgresql-simple-0.5.3.0.orig/postgresql-simple.cabal postgresql-simple-0.5.3.0/postgresql-simple.cabal ---- postgresql-simple-0.5.3.0.orig/postgresql-simple.cabal 2017-05-15 07:29:53.000000000 +0200 -+++ postgresql-simple-0.5.3.0/postgresql-simple.cabal 2017-09-17 11:22:56.734593260 +0200 -@@ -72,6 +72,7 @@ - transformers, - uuid-types >= 1.0.0, - scientific, -+ semigroups, - vector - - if !impl(ghc >= 7.6) -Only in postgresql-simple-0.5.3.0: postgresql-simple.cabal.orig -diff -ru postgresql-simple-0.5.3.0.orig/src/Database/PostgreSQL/Simple/HStore/Implementation.hs postgresql-simple-0.5.3.0/src/Database/PostgreSQL/Simple/HStore/Implementation.hs ---- postgresql-simple-0.5.3.0.orig/src/Database/PostgreSQL/Simple/HStore/Implementation.hs 2017-05-15 07:29:53.000000000 +0200 -+++ postgresql-simple-0.5.3.0/src/Database/PostgreSQL/Simple/HStore/Implementation.hs 2017-09-17 11:22:56.734593260 +0200 -@@ -34,6 +34,7 @@ - import qualified Data.Text.Lazy as TL - import Data.Typeable - import Data.Monoid(Monoid(..)) -+import Data.Semigroup - import Database.PostgreSQL.Simple.FromField - import Database.PostgreSQL.Simple.ToField - -@@ -59,19 +60,24 @@ - Empty -> BL.empty - Comma x -> BU.toLazyByteString x - --instance Monoid HStoreBuilder where -- mempty = Empty -- mappend Empty x = x -- mappend (Comma a) x -+instance Semigroup HStoreBuilder where -+ Empty <> x = x -+ Comma a <> x - = Comma (a `mappend` case x of - Empty -> mempty - Comma b -> char8 ',' `mappend` b) - -+instance Monoid HStoreBuilder where -+ mempty = Empty -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+ - class ToHStoreText a where - toHStoreText :: a -> HStoreText - - -- | Represents escape text, ready to be the key or value to a hstore value --newtype HStoreText = HStoreText Builder deriving (Typeable, Monoid) -+newtype HStoreText = HStoreText Builder deriving (Typeable, Semigroup, Monoid) - - instance ToHStoreText HStoreText where - toHStoreText = id -diff -ru postgresql-simple-0.5.3.0.orig/src/Database/PostgreSQL/Simple/Types.hs postgresql-simple-0.5.3.0/src/Database/PostgreSQL/Simple/Types.hs ---- postgresql-simple-0.5.3.0.orig/src/Database/PostgreSQL/Simple/Types.hs 2017-05-15 07:29:53.000000000 +0200 -+++ postgresql-simple-0.5.3.0/src/Database/PostgreSQL/Simple/Types.hs 2017-09-17 11:22:56.734593260 +0200 -@@ -1,4 +1,4 @@ --{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, GeneralizedNewtypeDeriving #-} -+{-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, GeneralizedNewtypeDeriving #-} - - ------------------------------------------------------------------------------ - -- | -@@ -33,7 +33,9 @@ - import Control.Arrow (first) - import Data.ByteString (ByteString) - import Data.Hashable (Hashable(hashWithSalt)) -+import Data.Foldable (toList) - import Data.Monoid (Monoid(..)) -+import Data.Semigroup - import Data.String (IsString(..)) - import Data.Typeable (Typeable) - import Data.ByteString.Builder ( stringUtf8 ) -@@ -87,11 +89,16 @@ - instance IsString Query where - fromString = Query . toByteString . stringUtf8 - -+instance Semigroup Query where -+ Query a <> Query b = Query (B.append a b) -+ {-# INLINE (<>) #-} -+ sconcat xs = Query (B.concat $ map fromQuery $ toList xs) -+ - instance Monoid Query where - mempty = Query B.empty -- mappend (Query a) (Query b) = Query (B.append a b) -- {-# INLINE mappend #-} -- mconcat xs = Query (B.concat (map fromQuery xs)) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | A single-value \"collection\". - -- -Only in postgresql-simple-0.5.3.0/src/Database/PostgreSQL/Simple: Types.hs.orig diff --git a/patches/primitive-0.6.2.0.patch b/patches/primitive-0.6.2.0.patch deleted file mode 100644 index 1005f59ba40312d60ca6fb08397638bbcbad7e27..0000000000000000000000000000000000000000 --- a/patches/primitive-0.6.2.0.patch +++ /dev/null @@ -1,89 +0,0 @@ -From 7e6e7b4667020b61986c60e0c2d642e700e7966d Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sat, 9 Sep 2017 13:08:41 -0400 -Subject: [PATCH] =?UTF-8?q?Adapt=20to=20the=20Semigroup=E2=80=93Monoid=20P?= - =?UTF-8?q?roposal=20(#65)?= -MIME-Version: 1.0 -Content-Type: text/plain; charset=UTF-8 -Content-Transfer-Encoding: 8bit - -* Adapt to the Semigroup–Monoid Proposal - -* GHC 8.0 fix - ---- - Data/Primitive/Array.hs | 12 +++++++++++- - Data/Primitive/SmallArray.hs | 10 ++++++++++ - 2 files changed, 21 insertions(+), 1 deletion(-) - -diff --git a/Data/Primitive/Array.hs b/Data/Primitive/Array.hs -index a0fa0ed..5a3afdc 100644 ---- a/Data/Primitive/Array.hs -+++ b/Data/Primitive/Array.hs -@@ -52,6 +52,9 @@ import Data.Foldable (Foldable(..), toList) - import Data.Traversable (Traversable(..)) - import Data.Monoid - #endif -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - - import Text.ParserCombinators.ReadP - -@@ -272,7 +275,7 @@ cloneArray :: Array a -- ^ source array - -> Array a - {-# INLINE cloneArray #-} - #if __GLASGOW_HASKELL__ >= 702 --cloneArray (Array arr#) (I# off#) (I# len#) -+cloneArray (Array arr#) (I# off#) (I# len#) - = case cloneArray# arr# off# len# of arr'# -> Array arr'# - #else - cloneArray arr off len = runST $ do -@@ -528,9 +531,16 @@ instance MonadZip Array where - instance MonadFix Array where - mfix f = let l = mfix (toList . f) in fromListN (length l) l - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup (Array a) where -+ (<>) = (<|>) -+#endif -+ - instance Monoid (Array a) where - mempty = empty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = (<|>) -+#endif - mconcat l = createArray sz (die "mconcat" "impossible") $ \ma -> - let go !_ [ ] = return () - go off (a:as) = -diff --git a/Data/Primitive/SmallArray.hs b/Data/Primitive/SmallArray.hs -index 0684a10..5de2f16 100644 ---- a/Data/Primitive/SmallArray.hs -+++ b/Data/Primitive/SmallArray.hs -@@ -77,6 +77,9 @@ import Data.Data - import Data.Foldable - import Data.Functor.Identity - import Data.Monoid -+#if MIN_VERSION_base(4,9,0) -+import qualified Data.Semigroup as Sem -+#endif - import Text.ParserCombinators.ReadPrec - import Text.Read - import Text.Read.Lex -@@ -575,9 +578,16 @@ instance MonadZip SmallArray where - instance MonadFix SmallArray where - mfix f = fromList . mfix $ toList . f - -+#if MIN_VERSION_base(4,9,0) -+instance Sem.Semigroup (SmallArray a) where -+ (<>) = (<|>) -+#endif -+ - instance Monoid (SmallArray a) where - mempty = empty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = (<|>) -+#endif - mconcat sas = createSmallArray n (die "mconcat" "impossible") $ \sma -> - fix ? 0 ? sas $ \go off l -> case l of - [] -> return () diff --git a/patches/profunctors-5.2.1.patch b/patches/profunctors-5.2.1.patch deleted file mode 100644 index 6bc6903be41dec1b015262132057450530c517e8..0000000000000000000000000000000000000000 --- a/patches/profunctors-5.2.1.patch +++ /dev/null @@ -1,108 +0,0 @@ -From 48bd5329b265c2b4d584a46ab5f486d8309d569a Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Fri, 8 Sep 2017 19:40:21 -0400 -Subject: [PATCH] =?UTF-8?q?Adapt=20to=20the=20Semigroup=E2=80=93Monoid=20P?= - =?UTF-8?q?roposal=20(#58)?= -MIME-Version: 1.0 -Content-Type: text/plain; charset=UTF-8 -Content-Transfer-Encoding: 8bit - ---- - CHANGELOG.markdown | 4 ++++ - profunctors.cabal | 1 + - src/Data/Profunctor/Closed.hs | 11 ++++++++--- - src/Data/Profunctor/Strong.hs | 9 +++++++-- - 4 files changed, 20 insertions(+), 5 deletions(-) - -diff --git a/CHANGELOG.markdown b/CHANGELOG.markdown -index 7b3cedc7..5882816d 100644 ---- a/CHANGELOG.markdown -+++ b/CHANGELOG.markdown -@@ -1,3 +1,7 @@ -+next -+---- -+* Add `Semigroup` instances for `Closure` and `Tambara` -+ - 5.2.1 - ----- - * Allow `base-orphans-0.6`. -diff --git a/profunctors.cabal b/profunctors.cabal -index fde49928..362e25c6 100644 ---- a/profunctors.cabal -+++ b/profunctors.cabal -@@ -35,6 +35,7 @@ library - comonad >= 4 && < 6, - contravariant >= 1 && < 2, - distributive >= 0.4.4 && < 1, -+ semigroups >= 0.11 && < 0.19, - tagged >= 0.4.4 && < 1, - transformers >= 0.2 && < 0.6 - -diff --git a/src/Data/Profunctor/Closed.hs b/src/Data/Profunctor/Closed.hs -index bb4447d5..06f88f28 100644 ---- a/src/Data/Profunctor/Closed.hs -+++ b/src/Data/Profunctor/Closed.hs -@@ -34,12 +34,12 @@ import Control.Comonad - import Data.Bifunctor.Product (Product(..)) - import Data.Bifunctor.Tannen (Tannen(..)) - import Data.Distributive --import Data.Monoid hiding (Product) - import Data.Profunctor.Adjunction - import Data.Profunctor.Monad - import Data.Profunctor.Strong - import Data.Profunctor.Types - import Data.Profunctor.Unsafe -+import Data.Semigroup hiding (Product) - import Data.Tagged - import Data.Tuple - import Prelude hiding ((.),id) -@@ -155,9 +155,14 @@ instance (Profunctor p, ArrowPlus p) => Alternative (Closure p a) where - empty = zeroArrow - f <|> g = f <+> g - --instance (Profunctor p, Arrow p, Monoid b) => Monoid (Closure p a b) where -+instance (Profunctor p, Arrow p, Semigroup b) => Semigroup (Closure p a b) where -+ (<>) = liftA2 (<>) -+ -+instance (Profunctor p, Arrow p, Semigroup b, Monoid b) => Monoid (Closure p a b) where - mempty = pure mempty -- mappend = liftA2 mappend -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | - -- @ -diff --git a/src/Data/Profunctor/Strong.hs b/src/Data/Profunctor/Strong.hs -index a36ca2a5..bde9bf11 100644 ---- a/src/Data/Profunctor/Strong.hs -+++ b/src/Data/Profunctor/Strong.hs -@@ -44,11 +44,11 @@ import Data.Bifunctor.Clown (Clown(..)) - import Data.Bifunctor.Product (Product(..)) - import Data.Bifunctor.Tannen (Tannen(..)) - import Data.Functor.Contravariant (Contravariant(..)) --import Data.Monoid hiding (Product) - import Data.Profunctor.Adjunction - import Data.Profunctor.Monad - import Data.Profunctor.Types - import Data.Profunctor.Unsafe -+import Data.Semigroup hiding (Product) - import Data.Tagged - import Data.Tuple - import Prelude hiding (id,(.)) -@@ -226,9 +226,14 @@ instance (Profunctor p, ArrowPlus p) => Alternative (Tambara p a) where - empty = zeroArrow - f <|> g = f <+> g - -+instance ArrowPlus p => Semigroup (Tambara p a b) where -+ f <> g = f <+> g -+ - instance ArrowPlus p => Monoid (Tambara p a b) where - mempty = zeroArrow -- mappend f g = f <+> g -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | - -- @ diff --git a/patches/protocol-buffers-2.4.6.patch b/patches/protocol-buffers-2.4.6.patch deleted file mode 100644 index 6a233e261468e44a5a1f71975dc42c37091ee351..0000000000000000000000000000000000000000 --- a/patches/protocol-buffers-2.4.6.patch +++ /dev/null @@ -1,50 +0,0 @@ -From c5e65330e1feb27d777cb8f04bb25779613c1b14 Mon Sep 17 00:00:00 2001 -From: Kostiantyn Rybnikov <k-bx@k-bx.com> -Date: Thu, 18 Jan 2018 17:20:39 +0200 -Subject: [PATCH] Add a Semigroup instance - ---- - Text/ProtocolBuffers/Basic.hs | 6 +++++- - protocol-buffers.cabal | 3 +++ - 2 files changed, 8 insertions(+), 1 deletion(-) - -diff --git a/Text/ProtocolBuffers/Basic.hs b/Text/ProtocolBuffers/Basic.hs -index 9bee937..88da387 100644 ---- a/Text/ProtocolBuffers/Basic.hs -+++ b/Text/ProtocolBuffers/Basic.hs -@@ -19,6 +19,7 @@ import Data.Foldable as F(Foldable(foldl)) - import Data.Generics(Data(..)) - import Data.Int(Int32,Int64) - import Data.Ix(Ix) -+import Data.Semigroup (Semigroup(..)) - #if __GLASGOW_HASKELL__ < 710 - import Data.Monoid(Monoid(..)) - #endif -@@ -51,9 +52,12 @@ instance Show Utf8 where - s = showsPrec - in s d (U.toString bs) - -+instance Semigroup Utf8 where -+ (<>) (Utf8 x) (Utf8 y) = Utf8 (x <> y) -+ - instance Monoid Utf8 where - mempty = Utf8 mempty -- mappend (Utf8 x) (Utf8 y) = Utf8 (mappend x y) -+ mappend = (<>) - - -- | 'WireTag' is the 32 bit value with the upper 29 bits being the - -- 'FieldId' and the lower 3 bits being the 'WireType' -diff --git a/protocol-buffers.cabal b/protocol-buffers.cabal -index d032e51..fec1fe6 100644 ---- a/protocol-buffers.cabal -+++ b/protocol-buffers.cabal -@@ -44,6 +44,9 @@ Library - parsec, - utf8-string, - syb -+ if !impl(ghc >= 8.0) -+ build-depends: -+ semigroups >= 0.11 && < 0.19 - - -- Most of these are needed for protocol-buffers (Get and WireMessage.hs) - -- Nothing especially hazardous in this list diff --git a/patches/protolude-0.2.2.patch b/patches/protolude-0.2.2.patch deleted file mode 100644 index a8dbcd7187c75c82cae42601bae32b78bdd26cb7..0000000000000000000000000000000000000000 --- a/patches/protolude-0.2.2.patch +++ /dev/null @@ -1,30 +0,0 @@ -diff -ru protolude-0.2.2.orig/src/Protolude/Base.hs protolude-0.2.2/src/Protolude/Base.hs ---- protolude-0.2.2.orig/src/Protolude/Base.hs 2018-02-05 11:35:26.000000000 -0500 -+++ protolude-0.2.2/src/Protolude/Base.hs 2018-07-04 21:24:34.620310887 -0400 -@@ -122,8 +122,10 @@ - - #if ( __GLASGOW_HASKELL__ >= 800 ) - import Data.Kind as X ( -- type (*) -- , type Type -+# if __GLASGOW_HASKELL__ < 805 -+ type (*), -+# endif -+ type Type - ) - #endif - -diff -ru protolude-0.2.2.orig/src/Protolude.hs protolude-0.2.2/src/Protolude.hs ---- protolude-0.2.2.orig/src/Protolude.hs 2018-03-26 06:36:35.000000000 -0400 -+++ protolude-0.2.2/src/Protolude.hs 2018-07-04 21:24:25.504310657 -0400 -@@ -492,8 +492,10 @@ - import Control.Monad.STM as X ( - STM - , atomically -+#if !(MIN_VERSION_stm(2,5,0)) - , always - , alwaysSucceeds -+#endif - , retry - , orElse - , check diff --git a/patches/psqueues-0.2.4.0.patch b/patches/psqueues-0.2.4.0.patch deleted file mode 100644 index df0739583be10c026219f60fe9970c9b1fae1702..0000000000000000000000000000000000000000 --- a/patches/psqueues-0.2.4.0.patch +++ /dev/null @@ -1,29 +0,0 @@ -commit 033a6319fd73edb76f5e87956791f565a1260b18 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue Jan 16 13:45:40 2018 -0500 - - Fix the build on GHC 8.4 - -diff --git a/src/Data/OrdPSQ/Internal.hs b/src/Data/OrdPSQ/Internal.hs -index a895e90..d69a127 100644 ---- a/src/Data/OrdPSQ/Internal.hs -+++ b/src/Data/OrdPSQ/Internal.hs -@@ -1,4 +1,5 @@ - {-# LANGUAGE BangPatterns #-} -+{-# LANGUAGE CPP #-} - {-# LANGUAGE DeriveFoldable #-} - {-# LANGUAGE DeriveFunctor #-} - {-# LANGUAGE DeriveTraversable #-} -@@ -74,7 +75,11 @@ import Data.Foldable (Foldable (foldr)) - import qualified Data.List as List - import Data.Maybe (isJust) - import Data.Traversable --import Prelude hiding (foldr, lookup, map, null) -+import Prelude hiding ( foldr, lookup, map, null -+#if MIN_VERSION_base(4,11,0) -+ , (<>) -+#endif -+ ) - - -------------------------------------------------------------------------------- - -- Types diff --git a/patches/reflection-2.1.2.patch b/patches/reflection-2.1.2.patch deleted file mode 100644 index f67594a5e7108ece3f37ad406a5fdde58dcd50d8..0000000000000000000000000000000000000000 --- a/patches/reflection-2.1.2.patch +++ /dev/null @@ -1,104 +0,0 @@ -From 4e53c744d8d0dbea7e975e20bce068cf3e425a58 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Fri, 8 Sep 2017 19:42:57 -0400 -Subject: [PATCH] =?UTF-8?q?Adapt=20to=20the=20Semigroup=E2=80=93Monoid=20P?= - =?UTF-8?q?roposal?= -MIME-Version: 1.0 -Content-Type: text/plain; charset=UTF-8 -Content-Transfer-Encoding: 8bit - - examples/Monoid.hs | 11 ++++++++--- - fast/Data/Reflection.hs | 10 ++++++++-- - -diff --git a/examples/Monoid.hs b/examples/Monoid.hs -index 22a05ff..838f20f 100644 ---- a/examples/Monoid.hs -+++ b/examples/Monoid.hs -@@ -1,6 +1,6 @@ --{-# LANGUAGE Rank2Types, FlexibleContexts, UndecidableInstances #-} -+{-# LANGUAGE CPP, Rank2Types, FlexibleContexts, UndecidableInstances #-} - import Data.Reflection -- from reflection --import Data.Monoid -- from base -+import Data.Semigroup -- from base - import Data.Proxy -- from tagged - - -- | Values in our dynamically-constructed 'Monoid' over 'a' -@@ -9,8 +9,13 @@ newtype M a s = M { runM :: a } deriving (Eq,Ord) - -- | A dictionary describing a 'Monoid' - data Monoid_ a = Monoid_ { mappend_ :: a -> a -> a, mempty_ :: a } - -+instance Reifies s (Monoid_ a) => Semigroup (M a s) where -+ a <> b = M $ mappend_ (reflect a) (runM a) (runM b) -+ - instance Reifies s (Monoid_ a) => Monoid (M a s) where -- mappend a b = M $ mappend_ (reflect a) (runM a) (runM b) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - mempty = a where a = M $ mempty_ (reflect a) - - -- Construct a 'Monoid' instance out of a binary operation and unit that you have in scope! -diff --git a/fast/Data/Reflection.hs b/fast/Data/Reflection.hs -index 5e98a73..1205001 100644 ---- a/fast/Data/Reflection.hs -+++ b/fast/Data/Reflection.hs -@@ -120,6 +120,7 @@ import Data.Foldable - import Data.Monoid - #endif - -+import Data.Semigroup as Sem - import Data.Proxy - - #if __GLASGOW_HASKELL__ < 710 -@@ -357,7 +358,7 @@ onProxyType1 f - | proxyName == ''Proxy = ConE 'Proxy `SigE` (ConT ''Proxy `AppT` f ta) - onProxyType1 f a = - LamE [SigP WildP na] body `AppE` a -- where -+ where - body = ConE 'Proxy `SigE` (ConT ''Proxy `AppT` f na) - na = VarT (mkName "na") - -@@ -552,8 +553,13 @@ reifyTypeable a k = unsafePerformIO $ do - - data ReifiedMonoid a = ReifiedMonoid { reifiedMappend :: a -> a -> a, reifiedMempty :: a } - -+instance Reifies s (ReifiedMonoid a) => Sem.Semigroup (ReflectedMonoid a s) where -+ ReflectedMonoid x <> ReflectedMonoid y = reflectResult (\m -> ReflectedMonoid (reifiedMappend m x y)) -+ - instance Reifies s (ReifiedMonoid a) => Monoid (ReflectedMonoid a s) where -- mappend (ReflectedMonoid x) (ReflectedMonoid y) = reflectResult (\m -> ReflectedMonoid (reifiedMappend m x y)) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - mempty = reflectResult (\m -> ReflectedMonoid (reifiedMempty m )) - - reflectResult :: forall f s a. Reifies s a => (a -> f s) -> f s -diff --git a/reflection.cabal b/reflection.cabal -index 4d42881..d33250f 100644 ---- a/reflection.cabal -+++ b/reflection.cabal -@@ -70,6 +70,10 @@ library - build-depends: - tagged >= 0.4.4 && < 1 - -+ if !impl(ghc >= 8.0) -+ build-depends: -+ semigroups >= 0.11 && < 0.19 -+ - default-language: Haskell98 - - if flag(template-haskell) && impl(ghc) -diff --git a/fast/Data/Reflection.hs b/fast/Data/Reflection.hs -index 1205001..26cbbd9 100644 ---- a/fast/Data/Reflection.hs -+++ b/fast/Data/Reflection.hs -@@ -117,7 +117,6 @@ import Data.Bits - - #if __GLASGOW_HASKELL__ < 710 - import Data.Foldable --import Data.Monoid - #endif - - import Data.Semigroup as Sem - diff --git a/patches/reflection-2.1.3.patch b/patches/reflection-2.1.3.patch deleted file mode 100644 index cf0a7d607dd457db6a721672dfae0a3891d8136c..0000000000000000000000000000000000000000 --- a/patches/reflection-2.1.3.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -ru reflection-2.1.3.orig/fast/Data/Reflection.hs reflection-2.1.3/fast/Data/Reflection.hs ---- reflection-2.1.3.orig/fast/Data/Reflection.hs 2018-01-18 19:35:38.000000000 -0500 -+++ reflection-2.1.3/fast/Data/Reflection.hs 2018-06-24 17:43:32.206218416 -0400 -@@ -330,7 +330,7 @@ - a + b = AppT (AppT (VarT ''(+)) a) b - - LitT (NumTyLit a) * LitT (NumTyLit b) = LitT (NumTyLit (a*b)) -- (*) a b = AppT (AppT (VarT ''(*)) a) b -+ (*) a b = AppT (AppT (VarT ''(GHC.TypeLits.*)) a) b - #if MIN_VERSION_base(4,8,0) - a - b = AppT (AppT (VarT ''(-)) a) b - #else diff --git a/patches/regex-tdfa-1.2.2.patch b/patches/regex-tdfa-1.2.2.patch deleted file mode 100644 index 6e7ec5f30f5195765d881d437ca8c041b18b0b1d..0000000000000000000000000000000000000000 --- a/patches/regex-tdfa-1.2.2.patch +++ /dev/null @@ -1,144 +0,0 @@ -diff -ru regex-tdfa-1.2.2.orig/Data/IntMap/CharMap2.hs regex-tdfa-1.2.2/Data/IntMap/CharMap2.hs ---- regex-tdfa-1.2.2.orig/Data/IntMap/CharMap2.hs 2016-04-28 13:04:18.000000000 +0200 -+++ regex-tdfa-1.2.2/Data/IntMap/CharMap2.hs 2017-09-17 11:11:02.246740925 +0200 -@@ -1,4 +1,5 @@ - {-# LANGUAGE CPP #-} -+{-# LANGUAGE GeneralizedNewtypeDeriving #-} - module Data.IntMap.CharMap2 where - - #ifdef __GLASGOW_HASKELL__ -@@ -6,6 +7,9 @@ - #else - import Data.Char (chr) - #endif -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Data.Char as C(ord) - import Data.List as L (map) - import qualified Data.IntMap as M -@@ -16,14 +20,12 @@ - unsafeChr = chr - #endif - --newtype CharMap a = CharMap {unCharMap :: M.IntMap a} deriving (Eq,Ord,Read,Show) -- --instance Monoid (CharMap a) where -- mempty = CharMap mempty -- CharMap x `mappend` CharMap y = CharMap (x `mappend` y) -- --instance Functor CharMap where -- fmap f (CharMap m) = CharMap (fmap f m) -+newtype CharMap a = CharMap {unCharMap :: M.IntMap a} -+ deriving (Eq,Ord,Read,Show,Functor,Monoid -+#if MIN_VERSION_base(4,9,0) -+ ,Semigroup -+#endif -+ ) - - type Key = Char - -diff -ru regex-tdfa-1.2.2.orig/Data/IntMap/EnumMap2.hs regex-tdfa-1.2.2/Data/IntMap/EnumMap2.hs ---- regex-tdfa-1.2.2.orig/Data/IntMap/EnumMap2.hs 2016-04-28 13:04:18.000000000 +0200 -+++ regex-tdfa-1.2.2/Data/IntMap/EnumMap2.hs 2017-09-17 11:11:02.246740925 +0200 -@@ -1,5 +1,10 @@ -+{-# LANGUAGE CPP #-} -+{-# LANGUAGE GeneralizedNewtypeDeriving #-} - module Data.IntMap.EnumMap2 where - -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Data.Foldable(Foldable(..)) - import qualified Data.IntMap as M - import qualified Data.IntSet.EnumSet2 as S (EnumSet(..)) -@@ -8,17 +13,11 @@ - import qualified Prelude as L (map) - - newtype EnumMap k a = EnumMap {unEnumMap :: M.IntMap a} -- deriving (Eq,Ord,Read,Show) -- --instance Ord k => Monoid (EnumMap k a) where -- mempty = EnumMap mempty -- EnumMap x `mappend` EnumMap y = EnumMap (x `mappend` y) -- --instance Ord k => Functor (EnumMap k) where -- fmap f (EnumMap m) = EnumMap (fmap f m) -- --instance Ord k => Foldable (EnumMap k) where -- foldMap f (EnumMap m) = foldMap f m -+ deriving (Eq,Ord,Read,Show,Monoid,Functor,Foldable -+#if MIN_VERSION_base(4,9,0) -+ ,Semigroup -+#endif -+ ) - - (!) :: (Enum key) => EnumMap key a -> key -> a - (!) (EnumMap m) k = (M.!) m (fromEnum k) -diff -ru regex-tdfa-1.2.2.orig/Data/IntSet/EnumSet2.hs regex-tdfa-1.2.2/Data/IntSet/EnumSet2.hs ---- regex-tdfa-1.2.2.orig/Data/IntSet/EnumSet2.hs 2016-04-28 13:04:18.000000000 +0200 -+++ regex-tdfa-1.2.2/Data/IntSet/EnumSet2.hs 2017-09-17 11:11:02.246740925 +0200 -@@ -1,15 +1,20 @@ -+{-# LANGUAGE CPP #-} -+{-# LANGUAGE GeneralizedNewtypeDeriving #-} - module Data.IntSet.EnumSet2 where - -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import qualified Data.IntSet as S - import qualified Data.List as L (map) - import Data.Monoid(Monoid(..)) - - newtype EnumSet e = EnumSet {unEnumSet :: S.IntSet} -- deriving (Eq,Ord,Read,Show) -- --instance Monoid (EnumSet e) where -- mempty = EnumSet mempty -- EnumSet x `mappend` EnumSet y = EnumSet (x `mappend` y) -+ deriving (Eq,Ord,Read,Show,Monoid -+#if MIN_VERSION_base(4,9,0) -+ ,Semigroup -+#endif -+ ) - - (\\) :: (Enum e) => EnumSet e -> EnumSet e -> EnumSet e - (\\) (EnumSet s1) (EnumSet s2) = EnumSet ((S.\\) s1 s2) -diff -ru regex-tdfa-1.2.2.orig/Text/Regex/TDFA/CorePattern.hs regex-tdfa-1.2.2/Text/Regex/TDFA/CorePattern.hs ---- regex-tdfa-1.2.2.orig/Text/Regex/TDFA/CorePattern.hs 2016-04-28 13:04:18.000000000 +0200 -+++ regex-tdfa-1.2.2/Text/Regex/TDFA/CorePattern.hs 2017-09-17 11:11:02.246740925 +0200 -@@ -30,10 +30,16 @@ - -- (start) looking for the first with an embedded PGroup can be found - -- and the PGroup free elements can be wrapped in some new PNOTAG - -- semantic indicator. -+ -+{-# LANGUAGE CPP #-} -+{-# LANGUAGE GeneralizedNewtypeDeriving #-} - module Text.Regex.TDFA.CorePattern(Q(..),P(..),WhichTest(..),Wanted(..) - ,TestInfo,OP(..),SetTestInfo(..),NullView - ,patternToQ,cleanNullView,cannotAccept,mustAccept) where - -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#endif - import Control.Monad.RWS {- all -} - import Data.Array.IArray(Array,(!),accumArray,listArray) - import Data.List(sort) -@@ -85,11 +91,12 @@ - - -- This is newtype'd to allow control over class instances - -- This is a set of WhichTest where each test has associated pattern location information --newtype SetTestInfo = SetTestInfo {getTests :: EnumMap WhichTest (EnumSet DoPa)} deriving (Eq) -- --instance Monoid SetTestInfo where -- mempty = SetTestInfo mempty -- SetTestInfo x `mappend` SetTestInfo y = SetTestInfo (x `mappend` y) -+newtype SetTestInfo = SetTestInfo {getTests :: EnumMap WhichTest (EnumSet DoPa)} -+ deriving (Eq,Monoid -+#if MIN_VERSION_base(4,9,0) -+ ,Semigroup -+#endif -+ ) - - instance Show SetTestInfo where - show (SetTestInfo sti) = "SetTestInfo "++show (mapSnd (Set.toList) $ Map.assocs sti) diff --git a/patches/repa-3.4.1.3.patch b/patches/repa-3.4.1.3.patch deleted file mode 100644 index 485e9a5fafe0f483fb2d89403df146b5e96c2c18..0000000000000000000000000000000000000000 --- a/patches/repa-3.4.1.3.patch +++ /dev/null @@ -1,21 +0,0 @@ -diff -ru repa-3.4.1.3.orig/repa.cabal repa-3.4.1.3/repa.cabal ---- repa-3.4.1.3.orig/repa.cabal 2017-08-20 22:51:56.000000000 -0400 -+++ repa-3.4.1.3/repa.cabal 2018-06-22 13:12:08.985456653 -0400 -@@ -30,7 +30,6 @@ - - ghc-options: - -Wall -fno-warn-missing-signatures -- -Odph - -funbox-strict-fields - - if impl(ghc >= 8.0) -@@ -38,6 +37,9 @@ - else - ghc-options: -fcpr-off - -+ if !impl(ghc >= 8.5) -+ ghc-options: -Odph -+ - extensions: - NoMonomorphismRestriction - ExplicitForAll diff --git a/patches/repa-algorithms-3.4.1.2.patch b/patches/repa-algorithms-3.4.1.2.patch deleted file mode 100644 index 298b9a0ee1db7274f5207cb1485dd0a6d5dbaef1..0000000000000000000000000000000000000000 --- a/patches/repa-algorithms-3.4.1.2.patch +++ /dev/null @@ -1,21 +0,0 @@ -diff -ru repa-algorithms-3.4.1.2.orig/repa-algorithms.cabal repa-algorithms-3.4.1.2/repa-algorithms.cabal ---- repa-algorithms-3.4.1.2.orig/repa-algorithms.cabal 2017-08-20 22:51:56.000000000 -0400 -+++ repa-algorithms-3.4.1.2/repa-algorithms.cabal 2018-06-22 13:15:08.149461165 -0400 -@@ -24,7 +24,6 @@ - - ghc-options: - -Wall -- -Odph - -fno-warn-missing-signatures - -fno-liberate-case - -fsimplifier-phases=4 -@@ -37,6 +36,9 @@ - else - ghc-options: -fcpr-off - -+ if !impl(ghc >= 8.5) -+ ghc-options: -Odph -+ - extensions: - NoMonomorphismRestriction - ExplicitForAll diff --git a/patches/repa-examples-3.4.1.1.patch b/patches/repa-examples-3.4.1.1.patch deleted file mode 100644 index b03573b54582d91cdb27d2c1c47bfac466feb54d..0000000000000000000000000000000000000000 --- a/patches/repa-examples-3.4.1.1.patch +++ /dev/null @@ -1,167 +0,0 @@ -diff -ru repa-examples-3.4.1.1.orig/repa-examples.cabal repa-examples-3.4.1.1/repa-examples.cabal ---- repa-examples-3.4.1.1.orig/repa-examples.cabal 2016-06-18 01:50:49.000000000 -0400 -+++ repa-examples-3.4.1.1/repa-examples.cabal 2018-06-22 13:19:58.997468489 -0400 -@@ -35,11 +35,13 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-mmult -@@ -57,13 +59,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-laplace -@@ -80,11 +84,13 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-fft2d -@@ -100,13 +106,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-fft2d-highpass -@@ -122,13 +130,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-fft3d-highpass -@@ -143,13 +153,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-blur -@@ -165,12 +177,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph -fno-liberate-case -+ -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-sobel -@@ -186,13 +201,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-volume -@@ -206,13 +223,15 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - - - Executable repa-unit-test -@@ -227,11 +246,13 @@ - -rtsopts - -threaded - -eventlog -- -Odph - -fno-liberate-case - -funfolding-use-threshold100 - -funfolding-keeness-factor100 - if flag(llvm) - ghc-options: - -fllvm -optlo-O3 -+ if !impl(ghc >= 8.5) -+ ghc-options: -+ -Odph - diff --git a/patches/safecopy-0.9.3.3.patch b/patches/safecopy-0.9.3.3.patch deleted file mode 100644 index 5a2e361a8d08d3194c8201266618c79b46ffeea6..0000000000000000000000000000000000000000 --- a/patches/safecopy-0.9.3.3.patch +++ /dev/null @@ -1,21 +0,0 @@ -diff -ru safecopy-0.9.3.3.orig/src/Data/SafeCopy/Instances.hs safecopy-0.9.3.3/src/Data/SafeCopy/Instances.hs ---- safecopy-0.9.3.3.orig/src/Data/SafeCopy/Instances.hs 2017-08-24 15:57:59.000000000 +0200 -+++ safecopy-0.9.3.3/src/Data/SafeCopy/Instances.hs 2017-09-17 11:15:41.269130588 +0200 -@@ -431,10 +431,15 @@ - typeName :: Typeable a => Proxy a -> String - typeName proxy = show (typeOf (undefined `asProxyType` proxy)) - -+#if MIN_VERSION_base(4,10,0) -+typeName1 :: (Typeable c) => Proxy (c a) -> String -+typeName2 :: (Typeable c) => Proxy (c a b) -> String -+#else - typeName1 :: (Typeable1 c) => Proxy (c a) -> String --typeName1 proxy = show (typeOf1 (undefined `asProxyType` proxy)) -- - typeName2 :: (Typeable2 c) => Proxy (c a b) -> String -+#endif -+ -+typeName1 proxy = show (typeOf1 (undefined `asProxyType` proxy)) - typeName2 proxy = show (typeOf2 (undefined `asProxyType` proxy)) - - getGenericVector :: (SafeCopy a, VG.Vector v a) => Contained (Get (v a)) diff --git a/patches/securemem-0.1.9.patch b/patches/securemem-0.1.9.patch deleted file mode 100644 index 069e7e49753a357514ca98fc961dd7678b477be4..0000000000000000000000000000000000000000 --- a/patches/securemem-0.1.9.patch +++ /dev/null @@ -1,35 +0,0 @@ -diff -ru securemem-0.1.9.orig/Data/SecureMem.hs securemem-0.1.9/Data/SecureMem.hs ---- securemem-0.1.9.orig/Data/SecureMem.hs 2015-06-02 15:37:32.000000000 +0200 -+++ securemem-0.1.9/Data/SecureMem.hs 2017-09-17 11:16:44.700762718 +0200 -@@ -31,7 +31,12 @@ - import Foreign.ForeignPtr (withForeignPtr) - import Foreign.Ptr - import Data.Word (Word8) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+import Data.Foldable (toList) -+#else - import Data.Monoid -+#endif - import Control.Applicative - import Data.Byteable - -@@ -96,10 +101,18 @@ - instance Eq SecureMem where - (==) = secureMemEq - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup SecureMem where -+ (<>) = secureMemAppend -+ sconcat = secureMemConcat . toList -+#endif -+ - instance Monoid SecureMem where - mempty = unsafeCreateSecureMem 0 (\_ -> return ()) -+#if !(MIN_VERSION_base(4,11,0)) - mappend = secureMemAppend - mconcat = secureMemConcat -+#endif - - -- | Types that can be converted to a secure mem object. - class ToSecureMem a where diff --git a/patches/semigroupoids-5.2.1.patch b/patches/semigroupoids-5.2.1.patch deleted file mode 100644 index 6a65adf435df312c2924bc1b7c94f31073be2280..0000000000000000000000000000000000000000 --- a/patches/semigroupoids-5.2.1.patch +++ /dev/null @@ -1,97 +0,0 @@ -From 39148303e6d223b91df238a7a6d68ae6dfe8fc58 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Fri, 8 Sep 2017 22:15:14 -0400 -Subject: [PATCH] =?UTF-8?q?Fix=20the=20build=20post-Semigroup=E2=80=93Mono?= - =?UTF-8?q?id=20Proposal=20(#61)?= -MIME-Version: 1.0 -Content-Type: text/plain; charset=UTF-8 -Content-Transfer-Encoding: 8bit - ---- - src/Data/Functor/Alt.hs | 8 +++++++- - src/Data/Functor/Bind/Trans.hs | 2 ++ - src/Data/Semigroup/Bitraversable.hs | 2 ++ - src/Data/Semigroup/Traversable.hs | 3 +++ - 4 files changed, 14 insertions(+), 1 deletion(-) - -diff --git a/src/Data/Functor/Alt.hs b/src/Data/Functor/Alt.hs -index 464891e..09b7227 100644 ---- a/src/Data/Functor/Alt.hs -+++ b/src/Data/Functor/Alt.hs -@@ -50,8 +50,8 @@ import Data.Functor.Bind - import Data.Functor.Compose - import Data.Functor.Product - import Data.Functor.Reverse --import Data.Semigroup hiding (Product) - import Data.List.NonEmpty (NonEmpty(..)) -+import Data.Semigroup (Option(..), Semigroup(..)) - import Prelude (($),Either(..),Maybe(..),const,IO,Ord,(++),(.),either,seq,undefined) - import Unsafe.Coerce - -@@ -61,6 +61,11 @@ import Data.IntMap (IntMap) - import Data.Sequence (Seq) - import qualified Data.Map as Map - import Data.Map (Map) -+# if MIN_VERSION_base(4,8,0) -+import Prelude (mappend) -+# else -+import Data.Monoid (mappend) -+# endif - #endif - - #if defined(MIN_VERSION_tagged) || (MIN_VERSION_base(4,7,0)) -@@ -73,6 +78,7 @@ import Generics.Deriving.Base - import GHC.Generics - #endif - -+ - infixl 3 <!> - - -- | Laws: -diff --git a/src/Data/Functor/Bind/Trans.hs b/src/Data/Functor/Bind/Trans.hs -index 805ce2a..7ff4224 100644 ---- a/src/Data/Functor/Bind/Trans.hs -+++ b/src/Data/Functor/Bind/Trans.hs -@@ -31,7 +31,9 @@ import qualified Control.Monad.Trans.State.Strict as Strict - import qualified Control.Monad.Trans.Writer.Strict as Strict - import Data.Functor.Bind - import Data.Orphans () -+#if !(MIN_VERSION_base(4,11,0)) - import Data.Semigroup hiding (Product) -+#endif - import Prelude hiding (id, (.)) - - -- | A subset of monad transformers can transform any 'Bind' as well. -diff --git a/src/Data/Semigroup/Bitraversable.hs b/src/Data/Semigroup/Bitraversable.hs -index b55433f..7bacbe3 100644 ---- a/src/Data/Semigroup/Bitraversable.hs -+++ b/src/Data/Semigroup/Bitraversable.hs -@@ -15,7 +15,9 @@ module Data.Semigroup.Bitraversable - ) where - - import Control.Applicative -+#if !(MIN_VERSION_base(4,11,0)) - import Data.Semigroup -+#endif - import Data.Semigroup.Traversable.Class - - bifoldMap1Default :: (Bitraversable1 t, Semigroup m) => (a -> m) -> (b -> m) -> t a b -> m -diff --git a/src/Data/Semigroup/Traversable.hs b/src/Data/Semigroup/Traversable.hs -index 5a8e19d..a9cc1e2 100644 ---- a/src/Data/Semigroup/Traversable.hs -+++ b/src/Data/Semigroup/Traversable.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - ----------------------------------------------------------------------------- - -- | - -- Copyright : (C) 2011-2015 Edward Kmett -@@ -14,7 +15,9 @@ module Data.Semigroup.Traversable - ) where - - import Control.Applicative -+#if !(MIN_VERSION_base(4,11,0)) - import Data.Semigroup -+#endif - import Data.Semigroup.Traversable.Class - - foldMap1Default :: (Traversable1 f, Semigroup m) => (a -> m) -> f a -> m diff --git a/patches/shake-0.16.4.patch b/patches/shake-0.16.4.patch deleted file mode 100644 index 66765904a4f48a0f68e33f3d5dbc2ae07deb718f..0000000000000000000000000000000000000000 --- a/patches/shake-0.16.4.patch +++ /dev/null @@ -1,23 +0,0 @@ -diff -ru shake-0.16.4.orig/src/General/FileLock.hs shake-0.16.4/src/General/FileLock.hs ---- shake-0.16.4.orig/src/General/FileLock.hs 2018-04-04 15:25:53.000000000 -0400 -+++ shake-0.16.4/src/General/FileLock.hs 2018-05-20 14:33:58.011899178 -0400 -@@ -60,7 +60,7 @@ - createDirectoryRecursive $ takeDirectory file - tryIO $ writeFile file "" - -- bracket (openFd file ReadWrite Nothing defaultFileFlags) closeFd $ \fd -> do -+ bracket (openSimpleFd file ReadWrite) closeFd $ \fd -> do - let lock = (WriteLock, AbsoluteSeek, 0, 0) - res <- tryIO $ setLock fd lock - case res of -@@ -73,4 +73,10 @@ - Just (pid, _) -> "Shake process ID " ++ show pid ++ " is using this lock.\n") ++ - show e - -+#if MIN_VERSION_unix(2,8,0) -+openSimpleFd file mode = openFd file mode defaultFileFlags -+#else -+openSimpleFd file mode = openFd file mode Nothing defaultFileFlags -+#endif -+ - #endif diff --git a/patches/shake-0.16.patch b/patches/shake-0.16.patch deleted file mode 100644 index 27beb817555bd3ea1e51605fde292ebf06607fce..0000000000000000000000000000000000000000 --- a/patches/shake-0.16.patch +++ /dev/null @@ -1,359 +0,0 @@ -From c2828063c49d515cc7a8e474fbc2c8a630fac699 Mon Sep 17 00:00:00 2001 -From: Moritz Angermann <moritz.angermann@gmail.com> -Date: Mon, 13 Nov 2017 14:37:41 +0800 -Subject: [PATCH 1/5] Semigroup-Monoid-Proposal changes - -Changes required to build against GHC HEAD. ---- - src/Development/Shake/Command.hs | 3 ++- - src/Development/Shake/Internal/Core/Rules.hs | 14 ++++++++++---- - src/Development/Shake/Internal/Progress.hs | 11 +++++++---- - src/General/Bilist.hs | 6 +++++- - src/General/Binary.hs | 7 +++++-- - src/General/ListBuilder.hs | 11 ++++++++--- - 6 files changed, 37 insertions(+), 15 deletions(-) - -diff --git a/src/Development/Shake/Command.hs b/src/Development/Shake/Command.hs -index 4bd26717..b28fb741 100644 ---- a/src/Development/Shake/Command.hs -+++ b/src/Development/Shake/Command.hs -@@ -30,6 +30,7 @@ import Data.Char - import Data.Either.Extra - import Data.List.Extra - import Data.Maybe -+import Data.Semigroup (Semigroup) - import Data.Monoid - import System.Directory - import System.Environment.Extra -@@ -586,7 +587,7 @@ cmd_ = cmd - - -- | The arguments to 'cmd' - see 'cmd' for examples and semantics. - newtype CmdArgument = CmdArgument [Either CmdOption String] -- deriving (Eq, Monoid, Show) -+ deriving (Eq, Semigroup, Monoid, Show) - - -- | The arguments to 'cmd' - see 'cmd' for examples and semantics. - class CmdArguments t where -diff --git a/src/Development/Shake/Internal/Core/Rules.hs b/src/Development/Shake/Internal/Core/Rules.hs -index 9f4a885a..f52031b3 100644 ---- a/src/Development/Shake/Internal/Core/Rules.hs -+++ b/src/Development/Shake/Internal/Core/Rules.hs -@@ -28,6 +28,7 @@ import qualified Data.HashMap.Strict as Map - import Data.Maybe - import System.IO.Extra - import System.IO.Unsafe -+import Data.Semigroup (Semigroup (..)) - import Data.Monoid - import qualified Data.ByteString.Lazy as LBS - import qualified Data.Binary.Builder as Bin -@@ -102,9 +103,8 @@ data SRules = SRules - ,userRules :: !(Map.HashMap TypeRep{-k-} UserRule_) - } - --instance Monoid SRules where -- mempty = SRules mempty Map.empty Map.empty -- mappend (SRules x1 x2 x3) (SRules y1 y2 y3) = SRules (mappend x1 y1) (Map.unionWithKey f x2 y2) (Map.unionWith g x3 y3) -+instance Semigroup SRules where -+ (SRules x1 x2 x3) <> (SRules y1 y2 y3) = SRules (mappend x1 y1) (Map.unionWithKey f x2 y2) (Map.unionWith g x3 y3) - where - f k _ _ = unsafePerformIO $ errorRuleDefinedMultipleTimes k - g (UserRule_ x) (UserRule_ y) = UserRule_ $ Unordered $ fromUnordered x ++ fromUnordered (fromJust $ cast y) -@@ -112,10 +112,16 @@ instance Monoid SRules where - fromUnordered (Unordered xs) = xs - fromUnordered x = [x] - -+instance Monoid SRules where -+ mempty = SRules mempty Map.empty Map.empty -+ mappend = (<>) -+ -+instance Semigroup a => Semigroup (Rules a) where -+ (<>) = liftA2 (<>) - - instance Monoid a => Monoid (Rules a) where - mempty = return mempty -- mappend = liftA2 mappend -+ mappend = (<>) - - - -- | Add a value of type 'UserRule'. -diff --git a/src/Development/Shake/Internal/Progress.hs b/src/Development/Shake/Internal/Progress.hs -index c04801f8..3b2b9668 100644 ---- a/src/Development/Shake/Internal/Progress.hs -+++ b/src/Development/Shake/Internal/Progress.hs -@@ -28,6 +28,7 @@ import General.Template - import System.IO.Unsafe - import Paths_shake - import System.Time.Extra -+import Data.Semigroup (Semigroup (..)) - import Data.Monoid - import Prelude - -@@ -66,10 +67,8 @@ data Progress = Progress - ,timeTodo :: {-# UNPACK #-} !(Double,Int) -- ^ Time spent building 'countTodo' rules in previous runs, plus the number which have no known time (have never been built before). - } - deriving (Eq,Ord,Show,Read,Data,Typeable) -- --instance Monoid Progress where -- mempty = Progress Nothing 0 0 0 0 0 0 0 (0,0) -- mappend a b = Progress -+instance Semigroup Progress where -+ a <> b = Progress - {isFailure = isFailure a `mplus` isFailure b - ,countSkipped = countSkipped a + countSkipped b - ,countBuilt = countBuilt a + countBuilt b -@@ -84,6 +83,10 @@ instance Monoid Progress where - } - - -+instance Monoid Progress where -+ mempty = Progress Nothing 0 0 0 0 0 0 0 (0,0) -+ mappend = (<>) -+ - --------------------------------------------------------------------- - -- MEALY TYPE - for writing the progress functions - -- See <http://hackage.haskell.org/package/machines-0.2.3.1/docs/Data-Machine-Mealy.html> -diff --git a/src/General/Bilist.hs b/src/General/Bilist.hs -index bf80be26..c9ed3042 100755 ---- a/src/General/Bilist.hs -+++ b/src/General/Bilist.hs -@@ -4,6 +4,7 @@ module General.Bilist( - Bilist, cons, snoc, uncons, toList, isEmpty - ) where - -+import Data.Semigroup (Semigroup(..)) - import Data.Monoid - import Prelude - -@@ -19,9 +20,12 @@ isEmpty (Bilist as bs) = null as && null bs - instance Eq a => Eq (Bilist a) where - a == b = toList a == toList b - -+instance Semigroup (Bilist a) where -+ a <> b = Bilist (toList a ++ toList b) [] -+ - instance Monoid (Bilist a) where - mempty = Bilist [] [] -- mappend a b = Bilist (toList a ++ toList b) [] -+ mappend = (<>) - - cons :: a -> Bilist a -> Bilist a - cons x (Bilist as bs) = Bilist (x:as) bs -diff --git a/src/General/Binary.hs b/src/General/Binary.hs -index 37f2e85c..c4aafa33 100644 ---- a/src/General/Binary.hs -+++ b/src/General/Binary.hs -@@ -22,6 +22,7 @@ import qualified Data.ByteString.Unsafe as BS - import qualified Data.ByteString.Lazy as LBS - import qualified Data.ByteString.UTF8 as UTF8 - import Data.Functor -+import Data.Semigroup (Semigroup (..)) - import Data.Monoid - import Prelude - -@@ -68,10 +69,12 @@ sizeBuilder (Builder i _) = i - runBuilder :: Builder -> BS.ByteString - runBuilder (Builder i f) = unsafePerformIO $ BS.create i $ \ptr -> f ptr 0 - -+instance Semigroup Builder where -+ (Builder x1 x2) <> (Builder y1 y2) = Builder (x1+y1) $ \p i -> do x2 p i; y2 p $ i+x1 -+ - instance Monoid Builder where - mempty = Builder 0 $ \_ _ -> return () -- mappend (Builder x1 x2) (Builder y1 y2) = Builder (x1+y1) $ \p i -> do x2 p i; y2 p $ i+x1 -- -+ mappend = (<>) - - -- | Methods for Binary serialisation that go directly between strict ByteString values. - -- When the Database is read each key/value will be loaded as a separate ByteString, -diff --git a/src/General/ListBuilder.hs b/src/General/ListBuilder.hs -index 70dcf32a..f20b6764 100755 ---- a/src/General/ListBuilder.hs -+++ b/src/General/ListBuilder.hs -@@ -3,6 +3,7 @@ module General.ListBuilder( - ListBuilder, runListBuilder, newListBuilder - ) where - -+import Data.Semigroup (Semigroup (..)) - import Data.Monoid - import Prelude() - -@@ -11,11 +12,15 @@ data ListBuilder a - | One a - | Add (ListBuilder a) (ListBuilder a) - -+ -+instance Semigroup (ListBuilder a) where -+ Zero <> x = x -+ x <> Zero = x -+ x <> y = Add x y -+ - instance Monoid (ListBuilder a) where - mempty = Zero -- mappend Zero x = x -- mappend x Zero = x -- mappend x y = Add x y -+ mappend = (<>) - - newListBuilder :: a -> ListBuilder a - newListBuilder = One - -From 739db1edfa61f1ec28702d259ac0e2156f36e066 Mon Sep 17 00:00:00 2001 -From: Moritz Angermann <moritz.angermann@gmail.com> -Date: Wed, 22 Nov 2017 10:41:57 +0800 -Subject: [PATCH 2/5] Adds semigroups dependencie for ghc < 8.0 - ---- - shake.cabal | 3 +++ - 1 file changed, 3 insertions(+) - -diff --git a/shake.cabal b/shake.cabal -index ca5fcdd3..f7227977 100644 ---- a/shake.cabal -+++ b/shake.cabal -@@ -106,6 +106,9 @@ library - if !os(windows) - build-depends: unix - -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups == 0.18.* -+ - exposed-modules: - Development.Shake - Development.Shake.Classes - -From 327451953ea994b33e6f429eee254ca04ab243ab Mon Sep 17 00:00:00 2001 -From: Moritz Angermann <moritz.angermann@gmail.com> -Date: Wed, 22 Nov 2017 10:59:46 +0800 -Subject: [PATCH 3/5] Hide (<>) from Monoid. - -It's exported from Semigroup already. ---- - src/Development/Shake/Internal/Core/Rules.hs | 2 +- - src/Development/Shake/Internal/Progress.hs | 2 +- - src/General/Bilist.hs | 2 +- - src/General/Binary.hs | 2 +- - src/General/ListBuilder.hs | 2 +- - 5 files changed, 5 insertions(+), 5 deletions(-) - -diff --git a/src/Development/Shake/Internal/Core/Rules.hs b/src/Development/Shake/Internal/Core/Rules.hs -index f52031b3..1455a45f 100644 ---- a/src/Development/Shake/Internal/Core/Rules.hs -+++ b/src/Development/Shake/Internal/Core/Rules.hs -@@ -29,7 +29,7 @@ import Data.Maybe - import System.IO.Extra - import System.IO.Unsafe - import Data.Semigroup (Semigroup (..)) --import Data.Monoid -+import Data.Monoid hiding ((<>)) - import qualified Data.ByteString.Lazy as LBS - import qualified Data.Binary.Builder as Bin - import Data.Binary.Put -diff --git a/src/Development/Shake/Internal/Progress.hs b/src/Development/Shake/Internal/Progress.hs -index 3b2b9668..b4b9d664 100644 ---- a/src/Development/Shake/Internal/Progress.hs -+++ b/src/Development/Shake/Internal/Progress.hs -@@ -29,7 +29,7 @@ import System.IO.Unsafe - import Paths_shake - import System.Time.Extra - import Data.Semigroup (Semigroup (..)) --import Data.Monoid -+import Data.Monoid hiding ((<>)) - import Prelude - - #ifdef mingw32_HOST_OS -diff --git a/src/General/Bilist.hs b/src/General/Bilist.hs -index c9ed3042..eb2dd767 100755 ---- a/src/General/Bilist.hs -+++ b/src/General/Bilist.hs -@@ -5,7 +5,7 @@ module General.Bilist( - ) where - - import Data.Semigroup (Semigroup(..)) --import Data.Monoid -+import Data.Monoid hiding ((<>)) - import Prelude - - -diff --git a/src/General/Binary.hs b/src/General/Binary.hs -index c4aafa33..4ed0a227 100644 ---- a/src/General/Binary.hs -+++ b/src/General/Binary.hs -@@ -23,7 +23,7 @@ import qualified Data.ByteString.Lazy as LBS - import qualified Data.ByteString.UTF8 as UTF8 - import Data.Functor - import Data.Semigroup (Semigroup (..)) --import Data.Monoid -+import Data.Monoid hiding ((<>)) - import Prelude - - -diff --git a/src/General/ListBuilder.hs b/src/General/ListBuilder.hs -index f20b6764..2952a45d 100755 ---- a/src/General/ListBuilder.hs -+++ b/src/General/ListBuilder.hs -@@ -4,7 +4,7 @@ module General.ListBuilder( - ) where - - import Data.Semigroup (Semigroup (..)) --import Data.Monoid -+import Data.Monoid hiding ((<>)) - import Prelude() - - data ListBuilder a - -From baf2700432d2694c408a57435382f987b9454c43 Mon Sep 17 00:00:00 2001 -From: Moritz Angermann <moritz.angermann@gmail.com> -Date: Wed, 22 Nov 2017 11:09:29 +0800 -Subject: [PATCH 4/5] Adds semigroup build dependency to all targets. - ---- - shake.cabal | 6 ++++++ - 1 file changed, 6 insertions(+) - -diff --git a/shake.cabal b/shake.cabal -index f7227977..eb85d6bf 100644 ---- a/shake.cabal -+++ b/shake.cabal -@@ -210,6 +210,9 @@ executable shake - if !os(windows) - build-depends: unix - -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups == 0.18.* -+ - other-modules: - Development.Ninja.All - Development.Ninja.Env -@@ -313,6 +316,9 @@ test-suite shake-test - if !os(windows) - build-depends: unix - -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups == 0.18.* -+ - other-modules: - Development.Ninja.All - Development.Ninja.Env - -From 79aad7aafe4504344b384a5a6d97c596c5fd73e0 Mon Sep 17 00:00:00 2001 -From: Moritz Angermann <moritz.angermann@gmail.com> -Date: Wed, 22 Nov 2017 11:29:52 +0800 -Subject: [PATCH 5/5] Adds semigrou constraint - ---- - src/Development/Shake/Internal/Core/Rules.hs | 2 +- - 1 file changed, 1 insertion(+), 1 deletion(-) - -diff --git a/src/Development/Shake/Internal/Core/Rules.hs b/src/Development/Shake/Internal/Core/Rules.hs -index 1455a45f..88c665f9 100644 ---- a/src/Development/Shake/Internal/Core/Rules.hs -+++ b/src/Development/Shake/Internal/Core/Rules.hs -@@ -119,7 +119,7 @@ instance Monoid SRules where - instance Semigroup a => Semigroup (Rules a) where - (<>) = liftA2 (<>) - --instance Monoid a => Monoid (Rules a) where -+instance (Semigroup a, Monoid a) => Monoid (Rules a) where - mempty = return mempty - mappend = (<>) - diff --git a/patches/shakespeare-2.0.14.1.patch b/patches/shakespeare-2.0.14.1.patch deleted file mode 100644 index 9b3782105596a64dacdbb3168b304867d693a3cb..0000000000000000000000000000000000000000 --- a/patches/shakespeare-2.0.14.1.patch +++ /dev/null @@ -1,90 +0,0 @@ -From 56b9635ffbe6b74f504211bbbd7280718f634bdf Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sun, 4 Feb 2018 18:51:52 -0500 -Subject: [PATCH] Add Semigroup instances for Javascript and Mixin - ---- - Text/Internal/Css.hs | 15 ++++++--------- - Text/Julius.hs | 5 +++-- - shakespeare.cabal | 3 +++ - 3 files changed, 12 insertions(+), 11 deletions(-) - -diff --git a/Text/Internal/Css.hs b/Text/Internal/Css.hs -index 852928b..9534216 100644 ---- a/Text/Internal/Css.hs -+++ b/Text/Internal/Css.hs -@@ -16,6 +16,7 @@ import Data.Text.Lazy.Builder (Builder, singleton, toLazyText, fromLazyText, fro - import qualified Data.Text.Lazy as TL - import qualified Data.Text.Lazy.Builder as TLB - import Data.Monoid (Monoid, mconcat, mappend, mempty) -+import Data.Semigroup (Semigroup(..)) - import Data.Text (Text) - import qualified Data.Text as T - import Language.Haskell.TH.Syntax -@@ -29,14 +30,6 @@ import Text.IndentToBrace (i2b) - import Data.Functor.Identity (runIdentity) - import Text.Shakespeare (VarType (..)) - --#if MIN_VERSION_base(4,5,0) --import Data.Monoid ((<>)) --#else --(<>) :: Monoid m => m -> m -> m --(<>) = mappend --{-# INLINE (<>) #-} --#endif -- - type CssUrl url = (url -> [(T.Text, T.Text)] -> T.Text) -> Css - - type DList a = [a] -> [a] -@@ -74,9 +67,13 @@ data Mixin = Mixin - { mixinAttrs :: ![Attr Resolved] - , mixinBlocks :: ![Block Resolved] - } -+instance Semigroup Mixin where -+ Mixin a x <> Mixin b y = Mixin (a ++ b) (x ++ y) - instance Monoid Mixin where - mempty = Mixin mempty mempty -- mappend (Mixin a x) (Mixin b y) = Mixin (a ++ b) (x ++ y) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - data TopLevel a where - TopBlock :: !(Block a) -> TopLevel a -diff --git a/Text/Julius.hs b/Text/Julius.hs -index 3ca06c2..9d65c65 100644 ---- a/Text/Julius.hs -+++ b/Text/Julius.hs -@@ -47,7 +47,8 @@ module Text.Julius - import Language.Haskell.TH.Quote (QuasiQuoter (..)) - import Language.Haskell.TH.Syntax - import Data.Text.Lazy.Builder (Builder, fromText, toLazyText, fromLazyText) --import Data.Monoid -+import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import qualified Data.Text as TS - import qualified Data.Text.Lazy as TL - import Text.Shakespeare -@@ -76,7 +77,7 @@ renderJavascriptUrl r s = renderJavascript $ s r - - -- | Newtype wrapper of 'Builder'. - newtype Javascript = Javascript { unJavascript :: Builder } -- deriving Monoid -+ deriving (Semigroup, Monoid) - - -- | Return type of template-reading functions. - type JavascriptUrl url = (url -> [(TS.Text, TS.Text)] -> TS.Text) -> Javascript -diff --git a/shakespeare.cabal b/shakespeare.cabal -index 77087a4..3ebd817 100644 ---- a/shakespeare.cabal -+++ b/shakespeare.cabal -@@ -53,6 +53,9 @@ library - , unordered-containers - , scientific >= 0.3.0.0 - -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups >= 0.16 -+ - exposed-modules: Text.Shakespeare.I18N - Text.Shakespeare.Text - Text.Roy diff --git a/patches/simple-reflect-0.3.2.patch b/patches/simple-reflect-0.3.2.patch deleted file mode 100644 index fbb9e7ad1f7c4afb99ba16b617bb82a819bee30e..0000000000000000000000000000000000000000 --- a/patches/simple-reflect-0.3.2.patch +++ /dev/null @@ -1,34 +0,0 @@ -diff -ru simple-reflect-0.3.2.orig/Debug/SimpleReflect/Expr.hs simple-reflect-0.3.2/Debug/SimpleReflect/Expr.hs ---- simple-reflect-0.3.2.orig/Debug/SimpleReflect/Expr.hs 2014-04-15 09:49:59.000000000 -0400 -+++ simple-reflect-0.3.2/Debug/SimpleReflect/Expr.hs 2017-12-28 12:24:08.448750835 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - ----------------------------------------------------------------------------- - -- | - -- Module : Debug.SimpleReflect.Expr -@@ -22,6 +23,9 @@ - - import Data.List - import Data.Monoid -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup -+#endif - import Control.Applicative - - ------------------------------------------------------------------------------ -@@ -220,8 +224,15 @@ - -- Other classes - ------------------------------------------------------------------------------ - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup Expr where -+ (<>) = withReduce2 $ op InfixR 6 " <> " -+#endif -+ - instance Monoid Expr where - mempty = var "mempty" -+#if !(MIN_VERSION_base(4,11,0)) - mappend = withReduce2 $ op InfixR 6 " <> " -+#endif - mconcat = fun "mconcat" - diff --git a/patches/singletons-2.3.1.patch b/patches/singletons-2.3.1.patch deleted file mode 100644 index 4e9dde99e02f74eb1c464b16f3370cbf14c1a026..0000000000000000000000000000000000000000 --- a/patches/singletons-2.3.1.patch +++ /dev/null @@ -1,143 +0,0 @@ -diff -ru singletons-2.3.1.orig/src/Data/Singletons/Partition.hs singletons-2.3.1/src/Data/Singletons/Partition.hs ---- singletons-2.3.1.orig/src/Data/Singletons/Partition.hs 2017-07-31 15:27:02.000000000 +0200 -+++ singletons-2.3.1/src/Data/Singletons/Partition.hs 2018-01-30 21:45:13.777063841 +0100 -@@ -26,7 +26,7 @@ - import Language.Haskell.TH.Desugar - import Data.Singletons.Util - --import Data.Monoid -+import Data.Semigroup - import Control.Monad - import Data.Maybe - -@@ -37,10 +37,13 @@ - , pd_data_decs :: [DataDecl] - } - -+instance Semigroup PartitionedDecs where -+ PDecs a1 b1 c1 d1 <> PDecs a2 b2 c2 d2 = -+ PDecs (a1 <> a2) (b1 <> b2) (c1 <> c2) (d1 <> d2) -+ - instance Monoid PartitionedDecs where - mempty = PDecs [] [] [] [] -- mappend (PDecs a1 b1 c1 d1) (PDecs a2 b2 c2 d2) = -- PDecs (a1 <> a2) (b1 <> b2) (c1 <> c2) (d1 <> d2) -+ mappend = (<>) - - -- | Split up a @[DDec]@ into its pieces, extracting 'Ord' instances - -- from deriving clauses -diff -ru singletons-2.3.1.orig/src/Data/Singletons/Promote/Monad.hs singletons-2.3.1/src/Data/Singletons/Promote/Monad.hs ---- singletons-2.3.1.orig/src/Data/Singletons/Promote/Monad.hs 2017-07-31 15:27:02.000000000 +0200 -+++ singletons-2.3.1/src/Data/Singletons/Promote/Monad.hs 2018-01-30 21:43:58.001392685 +0100 -@@ -9,7 +9,7 @@ - of DDec, and is wrapped around a Q. - -} - --{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, -+{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, StandaloneDeriving, - FlexibleContexts, TypeFamilies, KindSignatures #-} - - module Data.Singletons.Promote.Monad ( -@@ -46,7 +46,12 @@ - newtype PrM a = PrM (ReaderT PrEnv (WriterT [DDec] Q) a) - deriving ( Functor, Applicative, Monad, Quasi - , MonadReader PrEnv, MonadWriter [DDec] -- , MonadFail ) -+ , MonadFail -+#if MIN_VERSION_base(4,11,0) -+ , MonadIO -+#endif -+ ) -+ - - instance DsMonad PrM where - localDeclarations = asks pr_local_decls -diff -ru singletons-2.3.1.orig/src/Data/Singletons/Single/Monad.hs singletons-2.3.1/src/Data/Singletons/Single/Monad.hs ---- singletons-2.3.1.orig/src/Data/Singletons/Single/Monad.hs 2017-07-31 15:27:02.000000000 +0200 -+++ singletons-2.3.1/src/Data/Singletons/Single/Monad.hs 2018-01-30 21:44:55.425143522 +0100 -@@ -8,7 +8,7 @@ - The SgM monad allows reading from a SgEnv environment and is wrapped around a Q. - -} - --{-# LANGUAGE GeneralizedNewtypeDeriving, ParallelListComp, TemplateHaskell #-} -+{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, ParallelListComp, TemplateHaskell #-} - - module Data.Singletons.Single.Monad ( - SgM, bindLets, lookupVarE, lookupConE, -@@ -46,7 +46,11 @@ - newtype SgM a = SgM (ReaderT SgEnv (WriterT [DDec] Q) a) - deriving ( Functor, Applicative, Monad - , MonadReader SgEnv, MonadWriter [DDec] -- , MonadFail ) -+ , MonadFail -+#if MIN_VERSION_base(4,11,0) -+ , MonadIO -+#endif -+ ) - - liftSgM :: Q a -> SgM a - liftSgM = SgM . lift . lift -diff -ru singletons-2.3.1.orig/src/Data/Singletons/Syntax.hs singletons-2.3.1/src/Data/Singletons/Syntax.hs ---- singletons-2.3.1.orig/src/Data/Singletons/Syntax.hs 2017-07-31 15:27:02.000000000 +0200 -+++ singletons-2.3.1/src/Data/Singletons/Syntax.hs 2018-01-30 21:42:20.681814485 +0100 -@@ -13,7 +13,7 @@ - module Data.Singletons.Syntax where - - import Prelude hiding ( exp ) --import Data.Monoid -+import Data.Semigroup - import Language.Haskell.TH.Syntax - import Language.Haskell.TH.Desugar - import Data.Map.Strict ( Map ) -@@ -99,10 +99,13 @@ - type ALetDecEnv = LetDecEnv Annotated - type ULetDecEnv = LetDecEnv Unannotated - -+instance Semigroup ULetDecEnv where -+ LetDecEnv defns1 types1 infx1 _ <> LetDecEnv defns2 types2 infx2 _ = -+ LetDecEnv (defns1 <> defns2) (types1 <> types2) (infx1 <> infx2) () -+ - instance Monoid ULetDecEnv where - mempty = LetDecEnv Map.empty Map.empty [] () -- mappend (LetDecEnv defns1 types1 infx1 _) (LetDecEnv defns2 types2 infx2 _) = -- LetDecEnv (defns1 <> defns2) (types1 <> types2) (infx1 <> infx2) () -+ mappend = (<>) - - valueBinding :: Name -> ULetDecRHS -> ULetDecEnv - valueBinding n v = emptyLetDecEnv { lde_defns = Map.singleton n v } -diff -ru singletons-2.3.1.orig/src/Data/Singletons/TypeRepStar.hs singletons-2.3.1/src/Data/Singletons/TypeRepStar.hs ---- singletons-2.3.1.orig/src/Data/Singletons/TypeRepStar.hs 2017-07-31 15:27:02.000000000 +0200 -+++ singletons-2.3.1/src/Data/Singletons/TypeRepStar.hs 2018-01-30 21:37:38.371039144 +0100 -@@ -39,7 +39,6 @@ - import Data.Kind - import GHC.Exts ( Proxy# ) - import Data.Type.Coercion --import Data.Type.Equality - - data instance Sing (a :: *) where - STypeRep :: Typeable a => Sing a -@@ -52,7 +51,11 @@ - toSing = dirty_mk_STypeRep - - instance PEq Type where -- type (a :: *) :== (b :: *) = a == b -+ type (a :: *) :== (b :: *) = EqType a b -+ -+type family EqType (a :: Type) (b :: Type) where -+ EqType a a = 'True -+ EqType a b = 'False - - instance SEq Type where - (STypeRep :: Sing a) %:== (STypeRep :: Sing b) = -diff -ru singletons-2.3.1.orig/src/Data/Singletons/Util.hs singletons-2.3.1/src/Data/Singletons/Util.hs ---- singletons-2.3.1.orig/src/Data/Singletons/Util.hs 2017-07-31 15:27:02.000000000 +0200 -+++ singletons-2.3.1/src/Data/Singletons/Util.hs 2018-01-30 21:37:38.371039144 +0100 -@@ -353,7 +353,7 @@ - newtype QWithAux m q a = QWA { runQWA :: WriterT m q a } - deriving ( Functor, Applicative, Monad, MonadTrans - , MonadWriter m, MonadReader r -- , MonadFail ) -+ , MonadFail, MonadIO ) - - -- make a Quasi instance for easy lifting - instance (Quasi q, Monoid m) => Quasi (QWithAux m q) where diff --git a/patches/singletons-2.4.1.patch b/patches/singletons-2.4.1.patch deleted file mode 100644 index 9fd2fff2a70f8f27849b8872392260709dee0cc9..0000000000000000000000000000000000000000 --- a/patches/singletons-2.4.1.patch +++ /dev/null @@ -1,88 +0,0 @@ -commit 6eb213390729706e1840eaa67124caf26ac839f3 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue Apr 3 14:45:48 2018 -0400 - - Allow building with template-haskell-2.14 - - This requires adding some CPP to temporarily support two versions of - GHC (8.4 and HEAD). I'll file an issue as a reminder to remove this - CPP once we drop support for GHC 8.4. - -diff --git a/src/Data/Singletons/Single/Monad.hs b/src/Data/Singletons/Single/Monad.hs -index 7da2a7b..b1928b2 100644 ---- a/src/Data/Singletons/Single/Monad.hs -+++ b/src/Data/Singletons/Single/Monad.hs -@@ -8,7 +8,7 @@ This file defines the SgM monad and its operations, for use during singling. - The SgM monad allows reading from a SgEnv environment and is wrapped around a Q. - -} - --{-# LANGUAGE GeneralizedNewtypeDeriving, ParallelListComp, TemplateHaskell #-} -+{-# LANGUAGE GeneralizedNewtypeDeriving, ParallelListComp, TemplateHaskell, CPP #-} - - module Data.Singletons.Single.Monad ( - SgM, bindLets, lookupVarE, lookupConE, -@@ -72,7 +72,12 @@ instance Quasi SgM where - qReifyConStrictness = liftSgM `comp1` qReifyConStrictness - qIsExtEnabled = liftSgM `comp1` qIsExtEnabled - qExtsEnabled = liftSgM qExtsEnabled -+#if MIN_VERSION_template_haskell(2,14,0) -+ qAddForeignFilePath = liftSgM `comp2` qAddForeignFilePath -+ qAddTempFile = liftSgM `comp1` qAddTempFile -+#else - qAddForeignFile = liftSgM `comp2` qAddForeignFile -+#endif - qAddCorePlugin = liftSgM `comp1` qAddCorePlugin - - qRecover (SgM handler) (SgM body) = do -diff --git a/src/Data/Singletons/Util.hs b/src/Data/Singletons/Util.hs -index 271ade3..fb64fad 100644 ---- a/src/Data/Singletons/Util.hs -+++ b/src/Data/Singletons/Util.hs -@@ -11,7 +11,7 @@ Users of the package should not need to consult this file. - TemplateHaskell, GeneralizedNewtypeDeriving, - MultiParamTypeClasses, StandaloneDeriving, - UndecidableInstances, MagicHash, UnboxedTuples, -- LambdaCase, NoMonomorphismRestriction #-} -+ LambdaCase, NoMonomorphismRestriction, CPP #-} - - module Data.Singletons.Util where - -@@ -417,7 +417,12 @@ instance (Quasi q, Monoid m) => Quasi (QWithAux m q) where - qReifyConStrictness = lift `comp1` qReifyConStrictness - qIsExtEnabled = lift `comp1` qIsExtEnabled - qExtsEnabled = lift qExtsEnabled -+#if MIN_VERSION_template_haskell(2,14,0) -+ qAddForeignFilePath = lift `comp2` qAddForeignFilePath -+ qAddTempFile = lift `comp1` qAddTempFile -+#else - qAddForeignFile = lift `comp2` qAddForeignFile -+#endif - qAddCorePlugin = lift `comp1` qAddCorePlugin - - qRecover exp handler = do - -commit ddd353afa3c92a53c00f22919611f734eaa0f29f -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sat Jun 30 18:51:48 2018 -0400 - - PNum(type (*)) requires NoStarIsType - - This requires adding some CPP to temporarily support two versions of - GHC (8.4 and HEAD). I'll amend #324 as a reminder to remove this - CPP once we drop support for GHC 8.4. - -diff --git a/src/Data/Singletons/Prelude/Num.hs b/src/Data/Singletons/Prelude/Num.hs -index 9381afc..f1d00ab 100644 ---- a/src/Data/Singletons/Prelude/Num.hs -+++ b/src/Data/Singletons/Prelude/Num.hs -@@ -2,6 +2,10 @@ - TypeOperators, GADTs, ScopedTypeVariables, UndecidableInstances, - DefaultSignatures, FlexibleContexts, InstanceSigs - #-} -+{-# LANGUAGE CPP #-} -+#if __GLASGOW_HASKELL__ >= 805 -+{-# LANGUAGE NoStarIsType #-} -+#endif - - ----------------------------------------------------------------------------- - -- | diff --git a/patches/snap-server-1.0.3.3.patch b/patches/snap-server-1.0.3.3.patch deleted file mode 100644 index 0adace6088cfeb66a731538b64ca3c63104f8586..0000000000000000000000000000000000000000 --- a/patches/snap-server-1.0.3.3.patch +++ /dev/null @@ -1,104 +0,0 @@ -commit 31212777f14163e9870fd0aec4ac00f914fc710a -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Mon Feb 26 19:24:29 2018 -0500 - - Add a Semigroup instance for Config - -diff --git a/snap-server.cabal b/snap-server.cabal -index b821bae..c9d4b9b 100644 ---- a/snap-server.cabal -+++ b/snap-server.cabal -@@ -129,6 +129,9 @@ Library - EmptyDataDecls, - GeneralizedNewtypeDeriving - -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups >= 0.16 && < 0.19 -+ - if flag(portable) || os(windows) - cpp-options: -DPORTABLE - else -diff --git a/src/Snap/Internal/Http/Server/Config.hs b/src/Snap/Internal/Http/Server/Config.hs -index 4809d16..0345f88 100644 ---- a/src/Snap/Internal/Http/Server/Config.hs -+++ b/src/Snap/Internal/Http/Server/Config.hs -@@ -92,6 +92,9 @@ import Data.Maybe (isJust, isNothing) - import Data.Monoid (Monoid (..)) - #endif - import Data.Monoid (Last (Last, getLast)) -+#if !MIN_VERSION_base(4,11,0) -+import Data.Semigroup (Semigroup (..)) -+#endif - import qualified Data.Text as T - import qualified Data.Text.Encoding as T - #if MIN_VERSION_base(4,7,0) -@@ -286,31 +289,8 @@ emptyConfig = mempty - - - ------------------------------------------------------------------------------ --instance Monoid (Config m a) where -- mempty = Config -- { hostname = Nothing -- , accessLog = Nothing -- , errorLog = Nothing -- , locale = Nothing -- , port = Nothing -- , bind = Nothing -- , sslport = Nothing -- , sslbind = Nothing -- , sslcert = Nothing -- , sslchaincert = Nothing -- , sslkey = Nothing -- , unixsocket = Nothing -- , unixaccessmode = Nothing -- , compression = Nothing -- , verbose = Nothing -- , errorHandler = Nothing -- , defaultTimeout = Nothing -- , other = Nothing -- , proxyType = Nothing -- , startupHook = Nothing -- } -- -- a `mappend` b = Config -+instance Semigroup (Config m a) where -+ a <> b = Config - { hostname = ov hostname - , accessLog = ov accessLog - , errorLog = ov errorLog -@@ -337,6 +317,35 @@ instance Monoid (Config m a) where - ov f = getLast $! (mappend `on` (Last . f)) a b - - -+instance Monoid (Config m a) where -+ mempty = Config -+ { hostname = Nothing -+ , accessLog = Nothing -+ , errorLog = Nothing -+ , locale = Nothing -+ , port = Nothing -+ , bind = Nothing -+ , sslport = Nothing -+ , sslbind = Nothing -+ , sslcert = Nothing -+ , sslchaincert = Nothing -+ , sslkey = Nothing -+ , unixsocket = Nothing -+ , unixaccessmode = Nothing -+ , compression = Nothing -+ , verbose = Nothing -+ , errorHandler = Nothing -+ , defaultTimeout = Nothing -+ , other = Nothing -+ , proxyType = Nothing -+ , startupHook = Nothing -+ } -+ -+#if !MIN_VERSION_base(4,11,0) -+ mappend = (<>) -+#endif -+ -+ - ------------------------------------------------------------------------------ - -- | These are the default values for the options - defaultConfig :: MonadSnap m => Config m a diff --git a/patches/storable-record-0.0.3.1.patch b/patches/storable-record-0.0.3.1.patch deleted file mode 100644 index 72fe39a686025e5b479438a5d705271af4de2285..0000000000000000000000000000000000000000 --- a/patches/storable-record-0.0.3.1.patch +++ /dev/null @@ -1,93 +0,0 @@ -diff -ru storable-record-0.0.3.1.orig/src/Foreign/Storable/Record.hs storable-record-0.0.3.1/src/Foreign/Storable/Record.hs ---- storable-record-0.0.3.1.orig/src/Foreign/Storable/Record.hs 2016-01-10 05:55:14.000000000 -0500 -+++ storable-record-0.0.3.1/src/Foreign/Storable/Record.hs 2018-01-24 12:01:37.039464692 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {- | - Here we show an example of how to - define a Storable instance with this module. -@@ -70,6 +71,9 @@ - import Control.Applicative (Applicative(pure, (<*>)), ) - import Data.Functor.Compose (Compose(Compose), ) - import Data.Monoid (Monoid(mempty, mappend), ) -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - - import Foreign.Storable.FixedArray (roundUp, ) - import qualified Foreign.Storable as St -@@ -130,6 +134,12 @@ - - newtype Alignment = Alignment {deconsAlignment :: Int} - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup Alignment where -+ {-# INLINE (<>) #-} -+ Alignment x <> Alignment y = Alignment (lcm x y) -+#endif -+ - instance Monoid Alignment where - {-# INLINE mempty #-} - {-# INLINE mappend #-} -diff -ru storable-record-0.0.3.1.orig/src/Foreign/Storable/RecordMinimalSize.hs storable-record-0.0.3.1/src/Foreign/Storable/RecordMinimalSize.hs ---- storable-record-0.0.3.1.orig/src/Foreign/Storable/RecordMinimalSize.hs 2016-01-10 05:55:14.000000000 -0500 -+++ storable-record-0.0.3.1/src/Foreign/Storable/RecordMinimalSize.hs 2018-01-24 12:02:41.931466327 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {- | - Here we show an example of how to - define a Storable instance with this module. -@@ -73,6 +74,9 @@ - import Control.Applicative (Applicative(pure, (<*>)), ) - import Data.Functor.Compose (Compose(Compose), ) - import Data.Monoid (Monoid(mempty, mappend), ) -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - - import Foreign.Storable.FixedArray (roundUp, ) - import qualified Foreign.Storable as St -@@ -127,6 +131,12 @@ - - newtype Alignment = Alignment Int - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup Alignment where -+ {-# INLINE (<>) #-} -+ Alignment x <> Alignment y = Alignment (lcm x y) -+#endif -+ - instance Monoid Alignment where - {-# INLINE mempty #-} - {-# INLINE mappend #-} -diff -ru storable-record-0.0.3.1.orig/src/Foreign/Storable/RecordReaderPtr.hs storable-record-0.0.3.1/src/Foreign/Storable/RecordReaderPtr.hs ---- storable-record-0.0.3.1.orig/src/Foreign/Storable/RecordReaderPtr.hs 2016-01-10 05:55:14.000000000 -0500 -+++ storable-record-0.0.3.1/src/Foreign/Storable/RecordReaderPtr.hs 2018-01-24 12:03:35.347467672 -0500 -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {- | - Here we show an example of how to - define a Storable instance with this module. -@@ -73,6 +74,9 @@ - import Control.Applicative (Applicative(pure, (<*>)), ) - import Data.Functor.Compose (Compose(Compose), ) - import Data.Monoid (Monoid(mempty, mappend), ) -+#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - - import Foreign.Storable.FixedArray (roundUp, ) - import qualified Foreign.Storable as St -@@ -127,6 +131,12 @@ - - newtype Alignment = Alignment {deconsAlignment :: Int} - -+#if MIN_VERSION_base(4,9,0) -+instance Semigroup Alignment where -+ {-# INLINE (<>) #-} -+ Alignment x <> Alignment y = Alignment (lcm x y) -+#endif -+ - instance Monoid Alignment where - {-# INLINE mempty #-} - {-# INLINE mappend #-} diff --git a/patches/streaming-0.2.0.0.patch b/patches/streaming-0.2.0.0.patch deleted file mode 100644 index 4b01e7d07bdd42bebbde63b113f0f29ff2c3470e..0000000000000000000000000000000000000000 --- a/patches/streaming-0.2.0.0.patch +++ /dev/null @@ -1,74 +0,0 @@ -diff -ru streaming-0.2.0.0.orig/src/Data/Functor/Of.hs streaming-0.2.0.0/src/Data/Functor/Of.hs ---- streaming-0.2.0.0.orig/src/Data/Functor/Of.hs 2017-12-09 10:17:19.000000000 -0500 -+++ streaming-0.2.0.0/src/Data/Functor/Of.hs 2018-01-06 17:11:05.816767057 -0500 -@@ -1,7 +1,8 @@ - {-# LANGUAGE CPP, DeriveDataTypeable, DeriveTraversable, DeriveFoldable, - DeriveGeneric #-} - module Data.Functor.Of where --import Data.Monoid -+import Data.Monoid (Monoid (..)) -+import Data.Semigroup (Semigroup (..)) - import Control.Applicative - import Data.Traversable (Traversable) - import Data.Foldable (Foldable) -@@ -19,11 +20,17 @@ - Read, Show, Traversable, Typeable, Generic, Generic1) - infixr 5 :> - -+instance (Semigroup a, Semigroup b) => Semigroup (Of a b) where -+ (m :> w) <> (m' :> w') = (m <> m') :> (w <> w') -+ {-#INLINE (<>) #-} -+ - instance (Monoid a, Monoid b) => Monoid (Of a b) where - mempty = mempty :> mempty - {-#INLINE mempty #-} -+#if !(MIN_VERSION_base(4,11,0)) - mappend (m :> w) (m' :> w') = mappend m m' :> mappend w w' - {-#INLINE mappend #-} -+#endif - - instance Functor (Of a) where - fmap f (a :> x) = a :> f x -diff -ru streaming-0.2.0.0.orig/src/Streaming/Internal.hs streaming-0.2.0.0/src/Streaming/Internal.hs ---- streaming-0.2.0.0.orig/src/Streaming/Internal.hs 2017-12-09 12:35:01.000000000 -0500 -+++ streaming-0.2.0.0/src/Streaming/Internal.hs 2018-01-06 17:09:49.784765142 -0500 -@@ -94,7 +94,8 @@ - import Control.Applicative - import Data.Function ( on ) - import Control.Monad.Morph --import Data.Monoid (Monoid (..), (<>)) -+import Data.Monoid (Monoid (..)) -+import Data.Semigroup (Semigroup (..)) - import Data.Data (Typeable) - import Prelude hiding (splitAt) - import Data.Functor.Compose -@@ -295,11 +296,17 @@ - str <|> str' = zipsWith' liftA2 str str' - {-#INLINE (<|>) #-} - -+instance (Functor f, Monad m, Semigroup w) => Semigroup (Stream f m w) where -+ a <> b = a >>= \w -> fmap (w <>) b -+ {-#INLINE (<>) #-} -+ - instance (Functor f, Monad m, Monoid w) => Monoid (Stream f m w) where - mempty = return mempty - {-#INLINE mempty #-} -- mappend a b = a >>= \w -> fmap (w <>) b -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend a b = a >>= \w -> fmap (w `mappend`) b - {-#INLINE mappend #-} -+#endif - - instance (Applicative f, Monad m) => MonadPlus (Stream f m) where - mzero = empty -diff -ru streaming-0.2.0.0.orig/streaming.cabal streaming-0.2.0.0/streaming.cabal ---- streaming-0.2.0.0.orig/streaming.cabal 2018-01-06 14:14:32.644500285 -0500 -+++ streaming-0.2.0.0/streaming.cabal 2018-01-06 17:06:24.308759968 -0500 -@@ -217,6 +217,7 @@ - base >=4.8 && <5 - , mtl >=2.1 && <2.3 - , mmorph >=1.0 && <1.2 -+ , semigroups >= 0.18 && <0.19 - , transformers >=0.5 && <0.6 - , transformers-base < 0.5 - , exceptions > 0.5 && < 0.9 diff --git a/patches/stringbuilder-0.5.0.patch b/patches/stringbuilder-0.5.0.patch deleted file mode 100644 index 3ca8802a564663034648b98a078bfbcd7a14374e..0000000000000000000000000000000000000000 --- a/patches/stringbuilder-0.5.0.patch +++ /dev/null @@ -1,14 +0,0 @@ -diff --git a/src/Data/String/Builder.hs b/src/Data/String/Builder.hs -index 6e4fa71..7093e6b 100644 ---- a/src/Data/String/Builder.hs -+++ b/src/Data/String/Builder.hs -@@ -41,6 +41,9 @@ instance Monad BuilderM where - - type Builder = BuilderM () - -+instance Semigroup Builder where -+ (<>) = mappend -+ - instance Monoid Builder where - mempty = return () - a `mappend` b = a >> b diff --git a/patches/svg-builder-0.1.0.2.patch b/patches/svg-builder-0.1.0.2.patch deleted file mode 100644 index 36a945ceebce647e9d12a3ac5e858f59210cad61..0000000000000000000000000000000000000000 --- a/patches/svg-builder-0.1.0.2.patch +++ /dev/null @@ -1,62 +0,0 @@ -commit 3e61caf88904ceebceb26d94c4892df97aba5538 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 12:11:48 2018 -0500 - - Add a Semigroup Element instance - -diff --git a/src/Graphics/Svg/Core.hs b/src/Graphics/Svg/Core.hs -index 4a8fa9a..bd16b5e 100644 ---- a/src/Graphics/Svg/Core.hs -+++ b/src/Graphics/Svg/Core.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# LANGUAGE FlexibleInstances #-} - {-# LANGUAGE OverloadedStrings #-} - {-# LANGUAGE TypeFamilies #-} -@@ -39,7 +40,8 @@ import Data.ByteString.Lazy (ByteString) - import Data.Hashable (Hashable(..)) - import Data.HashMap.Strict (HashMap) - import qualified Data.HashMap.Strict as M --import Data.Monoid -+import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.String - import Data.Text (Text) - import qualified Data.Text.Lazy as LT -@@ -61,9 +63,14 @@ newtype Element = Element (HashMap Text Text -> Builder) - instance Show Element where - show e = LT.unpack . renderText $ e - -+instance Semigroup Element where -+ Element e1 <> Element e2 = Element (e1 <> e2) -+ - instance Monoid Element where - mempty = Element mempty -- mappend (Element e1) (Element e2) = Element (e1 <> e2) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - instance IsString Element where - fromString = toElement -@@ -140,7 +147,7 @@ makeElementNoEnd name = Element $ \a -> go a - - -- | Folding and monoidally appending attributes. - foldlMapWithKey :: Monoid m => (k -> v -> m) -> HashMap k v -> m --foldlMapWithKey f = M.foldlWithKey' (\m k v -> m <> f k v) mempty -+foldlMapWithKey f = M.foldlWithKey' (\m k v -> m `mappend` f k v) mempty - - s2b :: String -> Builder - s2b = BB.fromString -diff --git a/svg-builder.cabal b/svg-builder.cabal -index d0f0b33..7459839 100644 ---- a/svg-builder.cabal -+++ b/svg-builder.cabal -@@ -31,5 +31,7 @@ library - hashable >= 1.1 && < 1.3, - text >= 0.11 && < 1.3, - unordered-containers >= 0.2 && < 0.3 -+ if !impl(ghc >= 8.0) -+ build-depends: semigroups >= 0.16.1 && < 0.19 - hs-source-dirs: src - default-language: Haskell2010 diff --git a/patches/system-filepath-0.4.13.4.patch b/patches/system-filepath-0.4.13.4.patch deleted file mode 100644 index a7d38752b90ec03ec7bba59c49f62916955ba1ae..0000000000000000000000000000000000000000 --- a/patches/system-filepath-0.4.13.4.patch +++ /dev/null @@ -1,23 +0,0 @@ -diff -ru system-filepath-0.4.13.4.orig/lib/Filesystem/Path.hs system-filepath-0.4.13.4/lib/Filesystem/Path.hs ---- system-filepath-0.4.13.4.orig/lib/Filesystem/Path.hs 2015-05-12 09:50:07.000000000 +0200 -+++ system-filepath-0.4.13.4/lib/Filesystem/Path.hs 2017-09-14 22:23:05.751270598 +0200 -@@ -61,13 +61,17 @@ - import Data.List (foldl') - import Data.Maybe (isJust, isNothing) - import qualified Data.Monoid as M -+import qualified Data.Semigroup as S - import qualified Data.Text as T - - import Filesystem.Path.Internal - -+instance S.Semigroup FilePath where -+ (<>) = append -+ - instance M.Monoid FilePath where - mempty = empty -- mappend = append -+ mappend = (S.<>) - mconcat = concat - - ------------------------------------------------------------------------------- -Only in system-filepath-0.4.13.4/lib/Filesystem: Path.hs~ diff --git a/patches/tar-0.5.0.3.patch b/patches/tar-0.5.0.3.patch deleted file mode 100644 index 9cdafb700465d2973bb2ad7217289687b04f4175..0000000000000000000000000000000000000000 --- a/patches/tar-0.5.0.3.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ru tar-0.5.0.3.orig/Codec/Archive/Tar/Types.hs tar-0.5.0.3/Codec/Archive/Tar/Types.hs ---- tar-0.5.0.3.orig/Codec/Archive/Tar/Types.hs 2016-05-03 14:23:27.000000000 +0200 -+++ tar-0.5.0.3/Codec/Archive/Tar/Types.hs 2017-09-17 12:41:59.881183535 +0200 -@@ -62,6 +62,7 @@ - - import Data.Int (Int64) - import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import qualified Data.ByteString as BS - import qualified Data.ByteString.Char8 as BS.Char8 - import qualified Data.ByteString.Lazy as LBS -@@ -535,9 +536,12 @@ - mapEntriesNoFail f = - foldEntries (\entry -> Next (f entry)) Done Fail - -+instance Semigroup (Entries e) where -+ a <> b = foldEntries Next b Fail a -+ - instance Monoid (Entries e) where - mempty = Done -- mappend a b = foldEntries Next b Fail a -+ mappend = (<>) - - instance Functor Entries where - fmap f = foldEntries Next Done (Fail . f) -Only in tar-0.5.0.3/Codec/Archive/Tar: Types.hs~ diff --git a/patches/tasty-0.11.2.5.patch b/patches/tasty-0.11.2.5.patch deleted file mode 100644 index d43df946c0624326de1c9d0fdde3f7ec0f6accac..0000000000000000000000000000000000000000 --- a/patches/tasty-0.11.2.5.patch +++ /dev/null @@ -1,163 +0,0 @@ -diff -ru tasty-0.11.2.5.orig/tasty.cabal tasty-0.11.2.5/tasty.cabal ---- tasty-0.11.2.5.orig/tasty.cabal 2017-08-14 10:38:18.000000000 +0200 -+++ tasty-0.11.2.5/tasty.cabal 2017-09-17 11:26:48.153425316 +0200 -@@ -51,6 +51,7 @@ - stm >= 2.3, - containers, - mtl, -+ semigroups >= 0.17, - tagged >= 0.5, - regex-tdfa >= 1.1.8.2, - optparse-applicative >= 0.11, -diff -ru tasty-0.11.2.5.orig/Test/Tasty/Ingredients/ConsoleReporter.hs tasty-0.11.2.5/Test/Tasty/Ingredients/ConsoleReporter.hs ---- tasty-0.11.2.5.orig/Test/Tasty/Ingredients/ConsoleReporter.hs 2017-08-13 09:47:50.000000000 +0200 -+++ tasty-0.11.2.5/Test/Tasty/Ingredients/ConsoleReporter.hs 2017-09-17 11:26:48.153425316 +0200 -@@ -1,5 +1,5 @@ - -- vim:fdm=marker:foldtext=foldtext() --{-# LANGUAGE BangPatterns, ImplicitParams, MultiParamTypeClasses, DeriveDataTypeable, FlexibleContexts #-} -+{-# LANGUAGE CPP, BangPatterns, ImplicitParams, MultiParamTypeClasses, DeriveDataTypeable, FlexibleContexts #-} - -- | Console reporter ingredient - module Test.Tasty.Ingredients.ConsoleReporter - ( consoleTestReporter -@@ -23,7 +23,8 @@ - import qualified Data.IntMap as IntMap - import Data.Char - import Data.Maybe --import Data.Monoid -+import Data.Monoid (Monoid(..), Any(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.Proxy - import Data.Tagged - import Data.Typeable -@@ -48,11 +49,16 @@ - | Skip - | Seq TestOutput TestOutput - -+instance Semigroup TestOutput where -+ (<>) = Seq -+ - -- The monoid laws should hold observationally w.r.t. the semantics defined - -- in this module - instance Monoid TestOutput where - mempty = Skip -+#if !(MIN_VERSION_base(4,11,0)) - mappend = Seq -+#endif - - type Level = Int - -@@ -222,9 +228,14 @@ - , statFailures :: !Int - } - -+instance Semigroup Statistics where -+ Statistics t1 f1 <> Statistics t2 f2 = Statistics (t1 + t2) (f1 + f2) -+ - instance Monoid Statistics where -- Statistics t1 f1 `mappend` Statistics t2 f2 = Statistics (t1 + t2) (f1 + f2) - mempty = Statistics 0 0 -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - computeStatistics :: StatusMap -> IO Statistics - computeStatistics = getApp . foldMap (\var -> Ap $ -@@ -452,12 +463,16 @@ - = Maximum a - | MinusInfinity - -+instance Ord a => Semigroup (Maximum a) where -+ Maximum a <> Maximum b = Maximum (a `max` b) -+ MinusInfinity <> a = a -+ a <> MinusInfinity = a -+ - instance Ord a => Monoid (Maximum a) where - mempty = MinusInfinity -- -- Maximum a `mappend` Maximum b = Maximum (a `max` b) -- MinusInfinity `mappend` a = a -- a `mappend` MinusInfinity = a -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | Compute the amount of space needed to align "OK"s and "FAIL"s - computeAlignment :: OptionSet -> TestTree -> Int -diff -ru tasty-0.11.2.5.orig/Test/Tasty/Options.hs tasty-0.11.2.5/Test/Tasty/Options.hs ---- tasty-0.11.2.5.orig/Test/Tasty/Options.hs 2017-07-06 09:41:47.000000000 +0200 -+++ tasty-0.11.2.5/Test/Tasty/Options.hs 2017-09-17 11:26:48.153425316 +0200 -@@ -1,7 +1,7 @@ - {-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable, - ExistentialQuantification, GADTs, - OverlappingInstances, FlexibleInstances, UndecidableInstances, -- TypeOperators #-} -+ TypeOperators, CPP #-} - -- | Extensible options. They are used for provider-specific settings, - -- ingredient-specific settings and core settings (such as the test name pattern). - module Test.Tasty.Options -@@ -27,7 +27,8 @@ - import Data.Tagged - import Data.Proxy - import Data.Typeable --import Data.Monoid -+import Data.Semigroup (Semigroup(..)) -+import Data.Monoid (Monoid(..)) - import Data.Foldable - import Prelude -- Silence FTP import warnings - -@@ -77,11 +78,17 @@ - -- If some option has not been explicitly set, the default value is used. - newtype OptionSet = OptionSet (Map TypeRep OptionValue) - -+instance Semigroup OptionSet where -+ OptionSet a <> OptionSet b = -+ OptionSet $ Map.unionWith (flip const) a b -+ - -- | Later options override earlier ones - instance Monoid OptionSet where - mempty = OptionSet mempty -+#if !(MIN_VERSION_base(4,11,0)) - OptionSet a `mappend` OptionSet b = - OptionSet $ Map.unionWith (flip const) a b -+#endif - - -- | Set the option value - setOption :: IsOption v => v -> OptionSet -> OptionSet -diff -ru tasty-0.11.2.5.orig/Test/Tasty/Runners/Reducers.hs tasty-0.11.2.5/Test/Tasty/Runners/Reducers.hs ---- tasty-0.11.2.5.orig/Test/Tasty/Runners/Reducers.hs 2017-08-07 08:53:12.000000000 +0200 -+++ tasty-0.11.2.5/Test/Tasty/Runners/Reducers.hs 2017-09-17 11:26:48.153425316 +0200 -@@ -37,23 +37,33 @@ - POSSIBILITY OF SUCH DAMAGE. - -} - -+{-# LANGUAGE CPP #-} - {-# LANGUAGE GeneralizedNewtypeDeriving #-} - - module Test.Tasty.Runners.Reducers where - --import Data.Monoid -+import Data.Monoid hiding ((<>)) -+import Data.Semigroup (Semigroup(..)) - import Control.Applicative - import Prelude -- Silence AMP import warnings - - -- | Monoid generated by '*>' - newtype Traversal f = Traversal { getTraversal :: f () } -+instance Applicative f => Semigroup (Traversal f) where -+ Traversal f1 <> Traversal f2 = Traversal $ f1 *> f2 - instance Applicative f => Monoid (Traversal f) where - mempty = Traversal $ pure () -+#if !(MIN_VERSION_base(4,11,0)) - Traversal f1 `mappend` Traversal f2 = Traversal $ f1 *> f2 -+#endif - - -- | Monoid generated by @'liftA2' ('<>')@ - newtype Ap f a = Ap { getApp :: f a } - deriving (Functor, Applicative, Monad) -+instance (Applicative f, Semigroup a) => Semigroup (Ap f a) where -+ (<>) = liftA2 (<>) - instance (Applicative f, Monoid a) => Monoid (Ap f a) where - mempty = pure mempty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = liftA2 mappend -+#endif diff --git a/patches/tasty-0.11.3.patch b/patches/tasty-0.11.3.patch deleted file mode 100644 index 49bcececaa46989a7cb23f919994deb9655449d7..0000000000000000000000000000000000000000 --- a/patches/tasty-0.11.3.patch +++ /dev/null @@ -1,169 +0,0 @@ -Only in tasty-0.11.3: cabal.project -Only in tasty-0.11.3: dist -Only in tasty-0.11.3: dist-newstyle -Only in tasty-0.11.3: .ghc.environment.x86_64-linux-8.2.1 -Only in tasty-0.11.3: .ghc.environment.x86_64-linux-8.3.20171108 -diff -ru tasty-0.11.3.orig/tasty.cabal tasty-0.11.3/tasty.cabal ---- tasty-0.11.3.orig/tasty.cabal 2017-10-18 16:54:13.000000000 +0200 -+++ tasty-0.11.3/tasty.cabal 2017-11-10 20:47:06.974039938 +0100 -@@ -51,6 +51,7 @@ - stm >= 2.3, - containers, - mtl, -+ semigroups >= 0.17, - tagged >= 0.5, - regex-tdfa >= 1.1.8.2, - optparse-applicative >= 0.11, -diff -ru tasty-0.11.3.orig/Test/Tasty/Ingredients/ConsoleReporter.hs tasty-0.11.3/Test/Tasty/Ingredients/ConsoleReporter.hs ---- tasty-0.11.3.orig/Test/Tasty/Ingredients/ConsoleReporter.hs 2017-10-18 16:54:13.000000000 +0200 -+++ tasty-0.11.3/Test/Tasty/Ingredients/ConsoleReporter.hs 2017-11-10 20:47:06.974039938 +0100 -@@ -1,5 +1,5 @@ - -- vim:fdm=marker:foldtext=foldtext() --{-# LANGUAGE BangPatterns, ImplicitParams, MultiParamTypeClasses, DeriveDataTypeable, FlexibleContexts #-} -+{-# LANGUAGE CPP, BangPatterns, ImplicitParams, MultiParamTypeClasses, DeriveDataTypeable, FlexibleContexts #-} - -- | Console reporter ingredient - module Test.Tasty.Ingredients.ConsoleReporter - ( consoleTestReporter -@@ -37,7 +37,8 @@ - import qualified Data.IntMap as IntMap - import Data.Char - import Data.Maybe --import Data.Monoid -+import Data.Monoid (Monoid(..), Any(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.Proxy - import Data.Tagged - import Data.Typeable -@@ -68,11 +69,16 @@ - | Skip -- ^ Inactive test (e.g. not matching the current pattern) - | Seq TestOutput TestOutput -- ^ Two sets of 'TestOuput' on the same level - -+instance Semigroup TestOutput where -+ (<>) = Seq -+ - -- The monoid laws should hold observationally w.r.t. the semantics defined - -- in this module - instance Monoid TestOutput where - mempty = Skip -+#if !(MIN_VERSION_base(4,11,0)) - mappend = Seq -+#endif - - type Level = Int - -@@ -262,9 +268,14 @@ - , statFailures :: !Int -- ^ Number of active tests that failed. - } - -+instance Semigroup Statistics where -+ Statistics t1 f1 <> Statistics t2 f2 = Statistics (t1 + t2) (f1 + f2) -+ - instance Monoid Statistics where -- Statistics t1 f1 `mappend` Statistics t2 f2 = Statistics (t1 + t2) (f1 + f2) - mempty = Statistics 0 0 -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - computeStatistics :: StatusMap -> IO Statistics - computeStatistics = getApp . foldMap (\var -> Ap $ -@@ -504,12 +515,16 @@ - = Maximum a - | MinusInfinity - -+instance Ord a => Semigroup (Maximum a) where -+ Maximum a <> Maximum b = Maximum (a `max` b) -+ MinusInfinity <> a = a -+ a <> MinusInfinity = a -+ - instance Ord a => Monoid (Maximum a) where - mempty = MinusInfinity -- -- Maximum a `mappend` Maximum b = Maximum (a `max` b) -- MinusInfinity `mappend` a = a -- a `mappend` MinusInfinity = a -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | Compute the amount of space needed to align "OK"s and "FAIL"s - computeAlignment :: OptionSet -> TestTree -> Int -Only in tasty-0.11.3/Test/Tasty/Ingredients: ConsoleReporter.hs.orig -diff -ru tasty-0.11.3.orig/Test/Tasty/Options.hs tasty-0.11.3/Test/Tasty/Options.hs ---- tasty-0.11.3.orig/Test/Tasty/Options.hs 2017-07-06 09:41:47.000000000 +0200 -+++ tasty-0.11.3/Test/Tasty/Options.hs 2017-11-10 20:47:06.974039938 +0100 -@@ -1,7 +1,7 @@ - {-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable, - ExistentialQuantification, GADTs, - OverlappingInstances, FlexibleInstances, UndecidableInstances, -- TypeOperators #-} -+ TypeOperators, CPP #-} - -- | Extensible options. They are used for provider-specific settings, - -- ingredient-specific settings and core settings (such as the test name pattern). - module Test.Tasty.Options -@@ -27,7 +27,8 @@ - import Data.Tagged - import Data.Proxy - import Data.Typeable --import Data.Monoid -+import Data.Semigroup (Semigroup(..)) -+import Data.Monoid (Monoid(..)) - import Data.Foldable - import Prelude -- Silence FTP import warnings - -@@ -77,11 +78,17 @@ - -- If some option has not been explicitly set, the default value is used. - newtype OptionSet = OptionSet (Map TypeRep OptionValue) - -+instance Semigroup OptionSet where -+ OptionSet a <> OptionSet b = -+ OptionSet $ Map.unionWith (flip const) a b -+ - -- | Later options override earlier ones - instance Monoid OptionSet where - mempty = OptionSet mempty -+#if !(MIN_VERSION_base(4,11,0)) - OptionSet a `mappend` OptionSet b = - OptionSet $ Map.unionWith (flip const) a b -+#endif - - -- | Set the option value - setOption :: IsOption v => v -> OptionSet -> OptionSet -diff -ru tasty-0.11.3.orig/Test/Tasty/Runners/Reducers.hs tasty-0.11.3/Test/Tasty/Runners/Reducers.hs ---- tasty-0.11.3.orig/Test/Tasty/Runners/Reducers.hs 2017-08-07 08:53:12.000000000 +0200 -+++ tasty-0.11.3/Test/Tasty/Runners/Reducers.hs 2017-11-10 20:47:06.974039938 +0100 -@@ -37,23 +37,33 @@ - POSSIBILITY OF SUCH DAMAGE. - -} - -+{-# LANGUAGE CPP #-} - {-# LANGUAGE GeneralizedNewtypeDeriving #-} - - module Test.Tasty.Runners.Reducers where - --import Data.Monoid -+import Data.Monoid hiding ((<>)) -+import Data.Semigroup (Semigroup(..)) - import Control.Applicative - import Prelude -- Silence AMP import warnings - - -- | Monoid generated by '*>' - newtype Traversal f = Traversal { getTraversal :: f () } -+instance Applicative f => Semigroup (Traversal f) where -+ Traversal f1 <> Traversal f2 = Traversal $ f1 *> f2 - instance Applicative f => Monoid (Traversal f) where - mempty = Traversal $ pure () -+#if !(MIN_VERSION_base(4,11,0)) - Traversal f1 `mappend` Traversal f2 = Traversal $ f1 *> f2 -+#endif - - -- | Monoid generated by @'liftA2' ('<>')@ - newtype Ap f a = Ap { getApp :: f a } - deriving (Functor, Applicative, Monad) -+instance (Applicative f, Semigroup a) => Semigroup (Ap f a) where -+ (<>) = liftA2 (<>) - instance (Applicative f, Monoid a) => Monoid (Ap f a) where - mempty = pure mempty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = liftA2 mappend -+#endif diff --git a/patches/tasty-0.12.patch b/patches/tasty-0.12.patch deleted file mode 100644 index dc4f1c795a072a6298f33b417ed305d1104d8a67..0000000000000000000000000000000000000000 --- a/patches/tasty-0.12.patch +++ /dev/null @@ -1,168 +0,0 @@ -Only in tasty-0.12: cabal.project -Only in tasty-0.12: dist -Only in tasty-0.12: dist-newstyle -Only in tasty-0.12: .ghc.environment.x86_64-linux-8.3.20171108 -diff -ru tasty-0.12.orig/tasty.cabal tasty-0.12/tasty.cabal ---- tasty-0.12.orig/tasty.cabal 2017-11-01 15:46:33.000000000 +0100 -+++ tasty-0.12/tasty.cabal 2017-11-10 20:53:16.219997808 +0100 -@@ -51,6 +51,7 @@ - stm >= 2.3, - containers, - mtl, -+ semigroups >= 0.17, - tagged >= 0.5, - regex-tdfa >= 1.1.8.2, - optparse-applicative >= 0.11, -diff -ru tasty-0.12.orig/Test/Tasty/Ingredients/ConsoleReporter.hs tasty-0.12/Test/Tasty/Ingredients/ConsoleReporter.hs ---- tasty-0.12.orig/Test/Tasty/Ingredients/ConsoleReporter.hs 2017-11-01 15:46:33.000000000 +0100 -+++ tasty-0.12/Test/Tasty/Ingredients/ConsoleReporter.hs 2017-11-10 20:53:16.219997808 +0100 -@@ -1,5 +1,5 @@ - -- vim:fdm=marker:foldtext=foldtext() --{-# LANGUAGE BangPatterns, ImplicitParams, MultiParamTypeClasses, DeriveDataTypeable, FlexibleContexts #-} -+{-# LANGUAGE CPP, BangPatterns, ImplicitParams, MultiParamTypeClasses, DeriveDataTypeable, FlexibleContexts #-} - -- | Console reporter ingredient - module Test.Tasty.Ingredients.ConsoleReporter - ( consoleTestReporter -@@ -38,7 +38,8 @@ - import qualified Data.IntMap as IntMap - import Data.Char - import Data.Maybe --import Data.Monoid -+import Data.Monoid (Monoid(..), Any(..)) -+import Data.Semigroup (Semigroup(..)) - import Data.Proxy - import Data.Tagged - import Data.Typeable -@@ -70,11 +71,16 @@ - | Skip -- ^ Inactive test (e.g. not matching the current pattern) - | Seq TestOutput TestOutput -- ^ Two sets of 'TestOuput' on the same level - -+instance Semigroup TestOutput where -+ (<>) = Seq -+ - -- The monoid laws should hold observationally w.r.t. the semantics defined - -- in this module - instance Monoid TestOutput where - mempty = Skip -+#if !(MIN_VERSION_base(4,11,0)) - mappend = Seq -+#endif - - type Level = Int - -@@ -264,9 +270,14 @@ - , statFailures :: !Int -- ^ Number of active tests that failed. - } - -+instance Semigroup Statistics where -+ Statistics t1 f1 <> Statistics t2 f2 = Statistics (t1 + t2) (f1 + f2) -+ - instance Monoid Statistics where -- Statistics t1 f1 `mappend` Statistics t2 f2 = Statistics (t1 + t2) (f1 + f2) - mempty = Statistics 0 0 -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - computeStatistics :: StatusMap -> IO Statistics - computeStatistics = getApp . foldMap (\var -> Ap $ -@@ -515,12 +526,16 @@ - = Maximum a - | MinusInfinity - -+instance Ord a => Semigroup (Maximum a) where -+ Maximum a <> Maximum b = Maximum (a `max` b) -+ MinusInfinity <> a = a -+ a <> MinusInfinity = a -+ - instance Ord a => Monoid (Maximum a) where - mempty = MinusInfinity -- -- Maximum a `mappend` Maximum b = Maximum (a `max` b) -- MinusInfinity `mappend` a = a -- a `mappend` MinusInfinity = a -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | Compute the amount of space needed to align "OK"s and "FAIL"s - computeAlignment :: OptionSet -> TestTree -> Int -Only in tasty-0.12/Test/Tasty/Ingredients: ConsoleReporter.hs.orig -diff -ru tasty-0.12.orig/Test/Tasty/Options.hs tasty-0.12/Test/Tasty/Options.hs ---- tasty-0.12.orig/Test/Tasty/Options.hs 2017-07-06 09:41:47.000000000 +0200 -+++ tasty-0.12/Test/Tasty/Options.hs 2017-11-10 20:53:16.219997808 +0100 -@@ -1,7 +1,7 @@ - {-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable, - ExistentialQuantification, GADTs, - OverlappingInstances, FlexibleInstances, UndecidableInstances, -- TypeOperators #-} -+ TypeOperators, CPP #-} - -- | Extensible options. They are used for provider-specific settings, - -- ingredient-specific settings and core settings (such as the test name pattern). - module Test.Tasty.Options -@@ -27,7 +27,8 @@ - import Data.Tagged - import Data.Proxy - import Data.Typeable --import Data.Monoid -+import Data.Semigroup (Semigroup(..)) -+import Data.Monoid (Monoid(..)) - import Data.Foldable - import Prelude -- Silence FTP import warnings - -@@ -77,11 +78,17 @@ - -- If some option has not been explicitly set, the default value is used. - newtype OptionSet = OptionSet (Map TypeRep OptionValue) - -+instance Semigroup OptionSet where -+ OptionSet a <> OptionSet b = -+ OptionSet $ Map.unionWith (flip const) a b -+ - -- | Later options override earlier ones - instance Monoid OptionSet where - mempty = OptionSet mempty -+#if !(MIN_VERSION_base(4,11,0)) - OptionSet a `mappend` OptionSet b = - OptionSet $ Map.unionWith (flip const) a b -+#endif - - -- | Set the option value - setOption :: IsOption v => v -> OptionSet -> OptionSet -diff -ru tasty-0.12.orig/Test/Tasty/Runners/Reducers.hs tasty-0.12/Test/Tasty/Runners/Reducers.hs ---- tasty-0.12.orig/Test/Tasty/Runners/Reducers.hs 2017-08-07 08:53:12.000000000 +0200 -+++ tasty-0.12/Test/Tasty/Runners/Reducers.hs 2017-11-10 20:53:16.219997808 +0100 -@@ -37,23 +37,33 @@ - POSSIBILITY OF SUCH DAMAGE. - -} - -+{-# LANGUAGE CPP #-} - {-# LANGUAGE GeneralizedNewtypeDeriving #-} - - module Test.Tasty.Runners.Reducers where - --import Data.Monoid -+import Data.Monoid hiding ((<>)) -+import Data.Semigroup (Semigroup(..)) - import Control.Applicative - import Prelude -- Silence AMP import warnings - - -- | Monoid generated by '*>' - newtype Traversal f = Traversal { getTraversal :: f () } -+instance Applicative f => Semigroup (Traversal f) where -+ Traversal f1 <> Traversal f2 = Traversal $ f1 *> f2 - instance Applicative f => Monoid (Traversal f) where - mempty = Traversal $ pure () -+#if !(MIN_VERSION_base(4,11,0)) - Traversal f1 `mappend` Traversal f2 = Traversal $ f1 *> f2 -+#endif - - -- | Monoid generated by @'liftA2' ('<>')@ - newtype Ap f a = Ap { getApp :: f a } - deriving (Functor, Applicative, Monad) -+instance (Applicative f, Semigroup a) => Semigroup (Ap f a) where -+ (<>) = liftA2 (<>) - instance (Applicative f, Monoid a) => Monoid (Ap f a) where - mempty = pure mempty -+#if !(MIN_VERSION_base(4,11,0)) - mappend = liftA2 mappend -+#endif diff --git a/patches/tasty-1.1.0.1.patch b/patches/tasty-1.1.0.1.patch deleted file mode 100644 index dd31b71ee2ad04bee14ff6379a49209ddedbee7a..0000000000000000000000000000000000000000 --- a/patches/tasty-1.1.0.1.patch +++ /dev/null @@ -1,36 +0,0 @@ -diff -ru tasty-1.1.0.1.orig/Test/Tasty/CmdLine.hs tasty-1.1.0.1/Test/Tasty/CmdLine.hs ---- tasty-1.1.0.1.orig/Test/Tasty/CmdLine.hs 2018-02-12 13:46:24.000000000 -0500 -+++ tasty-1.1.0.1/Test/Tasty/CmdLine.hs 2018-06-05 07:52:59.307984985 -0400 -@@ -8,7 +8,7 @@ - ) where - - import Options.Applicative --import Data.Monoid -+import Data.Monoid (Monoid(..), (<>)) - import Data.Proxy - import Data.Foldable (foldMap) - import Prelude -- Silence AMP and FTP import warnings -diff -ru tasty-1.1.0.1.orig/Test/Tasty/Ingredients/ConsoleReporter.hs tasty-1.1.0.1/Test/Tasty/Ingredients/ConsoleReporter.hs ---- tasty-1.1.0.1.orig/Test/Tasty/Ingredients/ConsoleReporter.hs 2018-05-06 09:34:29.000000000 -0400 -+++ tasty-1.1.0.1/Test/Tasty/Ingredients/ConsoleReporter.hs 2018-06-05 07:52:07.023983669 -0400 -@@ -38,7 +38,7 @@ - import qualified Data.IntMap as IntMap - import Data.Char - import Data.Maybe --import Data.Monoid -+import Data.Monoid (Monoid(..), Any(..)) - import Data.Typeable - import Options.Applicative hiding (str) - import System.IO -diff -ru tasty-1.1.0.1.orig/Test/Tasty/Runners/Reducers.hs tasty-1.1.0.1/Test/Tasty/Runners/Reducers.hs ---- tasty-1.1.0.1.orig/Test/Tasty/Runners/Reducers.hs 2018-05-06 09:28:51.000000000 -0400 -+++ tasty-1.1.0.1/Test/Tasty/Runners/Reducers.hs 2018-06-05 07:52:07.023983669 -0400 -@@ -41,7 +41,7 @@ - - module Test.Tasty.Runners.Reducers where - --import Data.Monoid -+import Data.Monoid (Monoid(..)) - import Control.Applicative - import Prelude -- Silence AMP import warnings - #if MIN_VERSION_base(4,9,0) diff --git a/patches/tasty-1.1.0.2.patch b/patches/tasty-1.1.0.2.patch deleted file mode 100644 index f6dcb94c1e2c1c6b76ab2c905a3fd955d0545d1d..0000000000000000000000000000000000000000 --- a/patches/tasty-1.1.0.2.patch +++ /dev/null @@ -1,36 +0,0 @@ -diff -ru tasty-1.1.0.2.orig/Test/Tasty/CmdLine.hs tasty-1.1.0.2/Test/Tasty/CmdLine.hs ---- tasty-1.1.0.2.orig/Test/Tasty/CmdLine.hs 2018-02-12 13:46:24.000000000 -0500 -+++ tasty-1.1.0.2/Test/Tasty/CmdLine.hs 2018-06-30 18:36:35.559353670 -0400 -@@ -8,7 +8,7 @@ - ) where - - import Options.Applicative --import Data.Monoid -+import Data.Monoid (Monoid(..), (<>)) - import Data.Proxy - import Data.Foldable (foldMap) - import Prelude -- Silence AMP and FTP import warnings -diff -ru tasty-1.1.0.2.orig/Test/Tasty/Ingredients/ConsoleReporter.hs tasty-1.1.0.2/Test/Tasty/Ingredients/ConsoleReporter.hs ---- tasty-1.1.0.2.orig/Test/Tasty/Ingredients/ConsoleReporter.hs 2018-06-23 09:22:35.000000000 -0400 -+++ tasty-1.1.0.2/Test/Tasty/Ingredients/ConsoleReporter.hs 2018-06-30 18:37:05.631354427 -0400 -@@ -41,7 +41,7 @@ - import Data.Char.WCWidth (wcwidth) - #endif - import Data.Maybe --import Data.Monoid -+import Data.Monoid (Monoid(..), Any(..)) - import Data.Typeable - import Options.Applicative hiding (str) - import System.IO -diff -ru tasty-1.1.0.2.orig/Test/Tasty/Runners/Reducers.hs tasty-1.1.0.2/Test/Tasty/Runners/Reducers.hs ---- tasty-1.1.0.2.orig/Test/Tasty/Runners/Reducers.hs 2018-05-06 09:28:51.000000000 -0400 -+++ tasty-1.1.0.2/Test/Tasty/Runners/Reducers.hs 2018-06-30 18:35:50.635352539 -0400 -@@ -41,7 +41,7 @@ - - module Test.Tasty.Runners.Reducers where - --import Data.Monoid -+import Data.Monoid (Monoid(..)) - import Control.Applicative - import Prelude -- Silence AMP import warnings - #if MIN_VERSION_base(4,9,0) diff --git a/patches/test-framework-0.8.1.1.patch b/patches/test-framework-0.8.1.1.patch deleted file mode 100644 index 2e164715ef0516652783447765aafedfd92e260d..0000000000000000000000000000000000000000 --- a/patches/test-framework-0.8.1.1.patch +++ /dev/null @@ -1,346 +0,0 @@ -diff -ru test-framework-0.8.1.1.orig/Test/Framework/Options.hs test-framework-0.8.1.1/Test/Framework/Options.hs ---- test-framework-0.8.1.1.orig/Test/Framework/Options.hs 2015-01-09 05:04:37.000000000 +0100 -+++ test-framework-0.8.1.1/Test/Framework/Options.hs 2017-09-15 16:18:00.255689874 +0200 -@@ -4,7 +4,7 @@ - import Test.Framework.Utilities - - import Data.Monoid -- -+import Data.Semigroup (Semigroup(..)) - - type TestOptions = TestOptions' Maybe - type CompleteTestOptions = TestOptions' K -@@ -23,6 +23,17 @@ - -- ^ The number of microseconds to run tests for before considering them a failure - } - -+instance Semigroup (TestOptions' Maybe) where -+ to1 <> to2 = TestOptions { -+ topt_seed = getLast (mappendBy (Last . topt_seed) to1 to2), -+ topt_maximum_generated_tests = getLast (mappendBy (Last . topt_maximum_generated_tests) to1 to2), -+ topt_maximum_unsuitable_generated_tests = getLast (mappendBy (Last . topt_maximum_unsuitable_generated_tests) to1 to2), -+ topt_maximum_test_size = getLast (mappendBy (Last . topt_maximum_test_size) to1 to2), -+ topt_maximum_test_depth = getLast (mappendBy (Last . topt_maximum_test_depth) to1 to2), -+ topt_timeout = getLast (mappendBy (Last . topt_timeout) to1 to2) -+ } -+ -+ - instance Monoid (TestOptions' Maybe) where - mempty = TestOptions { - topt_seed = Nothing, -@@ -32,12 +43,4 @@ - topt_maximum_test_depth = Nothing, - topt_timeout = Nothing - } -- -- mappend to1 to2 = TestOptions { -- topt_seed = getLast (mappendBy (Last . topt_seed) to1 to2), -- topt_maximum_generated_tests = getLast (mappendBy (Last . topt_maximum_generated_tests) to1 to2), -- topt_maximum_unsuitable_generated_tests = getLast (mappendBy (Last . topt_maximum_unsuitable_generated_tests) to1 to2), -- topt_maximum_test_size = getLast (mappendBy (Last . topt_maximum_test_size) to1 to2), -- topt_maximum_test_depth = getLast (mappendBy (Last . topt_maximum_test_depth) to1 to2), -- topt_timeout = getLast (mappendBy (Last . topt_timeout) to1 to2) -- } -+ mappend = (<>) -Only in test-framework-0.8.1.1/Test/Framework: Options.hs~ -diff -ru test-framework-0.8.1.1.orig/Test/Framework/Runners/Options.hs test-framework-0.8.1.1/Test/Framework/Runners/Options.hs ---- test-framework-0.8.1.1.orig/Test/Framework/Runners/Options.hs 2015-01-09 05:04:37.000000000 +0100 -+++ test-framework-0.8.1.1/Test/Framework/Runners/Options.hs 2017-09-15 16:19:59.846945047 +0200 -@@ -8,6 +8,7 @@ - import Test.Framework.Runners.TestPattern - - import Data.Monoid -+import Data.Semigroup (Semigroup(..)) - - data ColorMode = ColorAuto | ColorNever | ColorAlways - -@@ -24,6 +25,18 @@ - ropt_list_only :: f Bool - } - -+instance Semigroup (RunnerOptions' Maybe) where -+ ro1 <> ro2 = RunnerOptions { -+ ropt_threads = getLast (mappendBy (Last . ropt_threads) ro1 ro2), -+ ropt_test_options = mappendBy ropt_test_options ro1 ro2, -+ ropt_test_patterns = mappendBy ropt_test_patterns ro1 ro2, -+ ropt_xml_output = mappendBy ropt_xml_output ro1 ro2, -+ ropt_xml_nested = getLast (mappendBy (Last . ropt_xml_nested) ro1 ro2), -+ ropt_color_mode = getLast (mappendBy (Last . ropt_color_mode) ro1 ro2), -+ ropt_hide_successes = getLast (mappendBy (Last . ropt_hide_successes) ro1 ro2), -+ ropt_list_only = getLast (mappendBy (Last . ropt_list_only) ro1 ro2) -+ } -+ - instance Monoid (RunnerOptions' Maybe) where - mempty = RunnerOptions { - ropt_threads = Nothing, -@@ -36,13 +49,4 @@ - ropt_list_only = Nothing - } - -- mappend ro1 ro2 = RunnerOptions { -- ropt_threads = getLast (mappendBy (Last . ropt_threads) ro1 ro2), -- ropt_test_options = mappendBy ropt_test_options ro1 ro2, -- ropt_test_patterns = mappendBy ropt_test_patterns ro1 ro2, -- ropt_xml_output = mappendBy ropt_xml_output ro1 ro2, -- ropt_xml_nested = getLast (mappendBy (Last . ropt_xml_nested) ro1 ro2), -- ropt_color_mode = getLast (mappendBy (Last . ropt_color_mode) ro1 ro2), -- ropt_hide_successes = getLast (mappendBy (Last . ropt_hide_successes) ro1 ro2), -- ropt_list_only = getLast (mappendBy (Last . ropt_list_only) ro1 ro2) -- } -+ mappend = (<>) -Only in test-framework-0.8.1.1/Test/Framework/Runners: Options.hs~ -diff -ru test-framework-0.8.1.1.orig/Test/Framework/Runners/Statistics.hs test-framework-0.8.1.1/Test/Framework/Runners/Statistics.hs ---- test-framework-0.8.1.1.orig/Test/Framework/Runners/Statistics.hs 2015-01-09 05:04:37.000000000 +0100 -+++ test-framework-0.8.1.1/Test/Framework/Runners/Statistics.hs 2017-09-15 16:21:06.214531462 +0200 -@@ -11,7 +11,7 @@ - import Data.Map (Map) - import qualified Data.Map as Map - import Data.Monoid -- -+import Data.Semigroup (Semigroup(..)) - - -- | Records a count of the various kinds of test that have been run - newtype TestCount = TestCount { unTestCount :: Map TestTypeName Int } -@@ -30,9 +30,12 @@ - testCountTotal :: TestCount -> Int - testCountTotal = sum . Map.elems . unTestCount - -+instance Semigroup TestCount where -+ (TestCount tcm1) <> (TestCount tcm2) = TestCount $ Map.unionWith (+) tcm1 tcm2 -+ - instance Monoid TestCount where - mempty = TestCount $ Map.empty -- mappend (TestCount tcm1) (TestCount tcm2) = TestCount $ Map.unionWith (+) tcm1 tcm2 -+ mappend = (<>) - - minusTestCount :: TestCount -> TestCount -> TestCount - minusTestCount (TestCount tcm1) (TestCount tcm2) = TestCount $ Map.unionWith (-) tcm1 tcm2 -@@ -48,9 +51,12 @@ - ts_failed_tests :: TestCount - } - -+instance Semigroup TestStatistics where -+ (TestStatistics tot1 run1 pas1 fai1) <> (TestStatistics tot2 run2 pas2 fai2) = TestStatistics (tot1 `mappend` tot2) (run1 `mappend` run2) (pas1 `mappend` pas2) (fai1 `mappend` fai2) -+ - instance Monoid TestStatistics where - mempty = TestStatistics mempty mempty mempty mempty -- mappend (TestStatistics tot1 run1 pas1 fai1) (TestStatistics tot2 run2 pas2 fai2) = TestStatistics (tot1 `mappend` tot2) (run1 `mappend` run2) (pas1 `mappend` pas2) (fai1 `mappend` fai2) -+ mappend = (<>) - - ts_pending_tests :: TestStatistics -> TestCount - ts_pending_tests ts = ts_total_tests ts `minusTestCount` ts_run_tests ts -Only in test-framework-0.8.1.1/Test/Framework/Runners: Statistics.hs~ -diff -ru test-framework-0.8.1.1.orig/test-framework.cabal test-framework-0.8.1.1/test-framework.cabal ---- test-framework-0.8.1.1.orig/test-framework.cabal 2015-01-09 05:04:37.000000000 +0100 -+++ test-framework-0.8.1.1/test-framework.cabal 2017-09-15 16:16:42.372174637 +0200 -@@ -1,104 +1,106 @@ --Name: test-framework --Version: 0.8.1.1 --Cabal-Version: >= 1.6 --Category: Testing --Synopsis: Framework for running and organising tests, with HUnit and QuickCheck support --Description: Allows tests such as QuickCheck properties and HUnit test cases to be assembled into test groups, run in -- parallel (but reported in deterministic order, to aid diff interpretation) and filtered and controlled by -- command line options. All of this comes with colored test output, progress reporting and test statistics output. --License: BSD3 --License-File: LICENSE --Author: Max Bolingbroke <batterseapower@hotmail.com> --Maintainer: Libraries List <libraries@haskell.org> --Homepage: https://batterseapower.github.io/test-framework/ --Bug-Reports: https://github.com/haskell/test-framework/issues/ --Build-Type: Simple -- --Flag Tests -- Description: Build the tests -- Default: False -- -- --Library -- Exposed-Modules: Test.Framework -- Test.Framework.Options -- Test.Framework.Providers.API -- Test.Framework.Runners.Console -- Test.Framework.Runners.Options -- Test.Framework.Runners.TestPattern -- Test.Framework.Runners.API -- Test.Framework.Seed -- -- Other-Modules: Test.Framework.Core -- Test.Framework.Improving -- Test.Framework.Runners.Console.Colors -- Test.Framework.Runners.Console.ProgressBar -- Test.Framework.Runners.Console.Run -- Test.Framework.Runners.Console.Statistics -- Test.Framework.Runners.Console.Table -- Test.Framework.Runners.Console.Utilities -- Test.Framework.Runners.Core -- Test.Framework.Runners.Processors -- Test.Framework.Runners.Statistics -- Test.Framework.Runners.ThreadPool -- Test.Framework.Runners.TimedConsumption -- Test.Framework.Runners.XML.JUnitWriter -- Test.Framework.Runners.XML -- Test.Framework.Utilities -- -- Build-Depends: ansi-terminal >= 0.4.0, ansi-wl-pprint >= 0.5.1, -- base >= 4.3 && < 5, random >= 1.0, containers >= 0.1, -- regex-posix >= 0.72, -- old-locale >= 1.0, -- time >= 1.1.2 && < 1.6, -- xml >= 1.3.5, hostname >= 1.0 -- -- Extensions: CPP -- PatternGuards -- ExistentialQuantification -- RecursiveDo -- FlexibleInstances -- TypeSynonymInstances -- TypeOperators -- FunctionalDependencies -- MultiParamTypeClasses -- -- Ghc-Options: -Wall -- -- if impl(ghc) -- Cpp-Options: -DCOMPILER_GHC -- --Executable test-framework-tests -- Main-Is: Test/Framework/Tests.hs -- -- if !flag(tests) -- Buildable: False -- else -- Build-Depends: HUnit >= 1.2, QuickCheck >= 2.3 && < 2.5, -- base >= 4.3 && < 5, random >= 1.0, containers >= 0.1, -- ansi-terminal >= 0.4.0, ansi-wl-pprint >= 0.5.1, -- regex-posix >= 0.72, -- old-locale >= 1.0, time >= 1.1.2, -- xml >= 1.3.5, hostname >= 1.0, -- libxml >= 0.1.1, bytestring >= 0.9 -- -- Extensions: CPP -- PatternGuards -- ExistentialQuantification -- RecursiveDo -- FlexibleInstances -- TypeSynonymInstances -- TypeOperators -- FunctionalDependencies -- MultiParamTypeClasses -- -- Cpp-Options: -DTEST -- -- Ghc-Options: -Wall -threaded -- -- if impl(ghc) -- Cpp-Options: -DCOMPILER_GHC -- --Source-Repository head -- Type: git -- Location: https://github.com/haskell/test-framework -+Name: test-framework -+Version: 0.8.1.1 -+x-revision: 2 -+Cabal-Version: >= 1.6 -+Category: Testing -+Synopsis: Framework for running and organising tests, with HUnit and QuickCheck support -+Description: Allows tests such as QuickCheck properties and HUnit test cases to be assembled into test groups, run in -+ parallel (but reported in deterministic order, to aid diff interpretation) and filtered and controlled by -+ command line options. All of this comes with colored test output, progress reporting and test statistics output. -+License: BSD3 -+License-File: LICENSE -+Author: Max Bolingbroke <batterseapower@hotmail.com> -+Maintainer: Libraries List <libraries@haskell.org> -+Homepage: https://batterseapower.github.io/test-framework/ -+Bug-Reports: https://github.com/haskell/test-framework/issues/ -+Build-Type: Simple -+ -+Flag Tests -+ Description: Build the tests -+ Default: False -+ Manual: True -+ -+ -+Library -+ Exposed-Modules: Test.Framework -+ Test.Framework.Options -+ Test.Framework.Providers.API -+ Test.Framework.Runners.Console -+ Test.Framework.Runners.Options -+ Test.Framework.Runners.TestPattern -+ Test.Framework.Runners.API -+ Test.Framework.Seed -+ -+ Other-Modules: Test.Framework.Core -+ Test.Framework.Improving -+ Test.Framework.Runners.Console.Colors -+ Test.Framework.Runners.Console.ProgressBar -+ Test.Framework.Runners.Console.Run -+ Test.Framework.Runners.Console.Statistics -+ Test.Framework.Runners.Console.Table -+ Test.Framework.Runners.Console.Utilities -+ Test.Framework.Runners.Core -+ Test.Framework.Runners.Processors -+ Test.Framework.Runners.Statistics -+ Test.Framework.Runners.ThreadPool -+ Test.Framework.Runners.TimedConsumption -+ Test.Framework.Runners.XML.JUnitWriter -+ Test.Framework.Runners.XML -+ Test.Framework.Utilities -+ -+ Build-Depends: ansi-terminal >= 0.4.0, ansi-wl-pprint >= 0.5.1, -+ base >= 4.3 && < 5, random >= 1.0 && < 2, containers >= 0.1, -+ regex-posix >= 0.72, -+ old-locale == 1.0.*, -+ time >= 1.1.2 && < 1.9, -+ xml >= 1.3.5, hostname >= 1.0 -+ -+ Extensions: CPP -+ PatternGuards -+ ExistentialQuantification -+ RecursiveDo -+ FlexibleInstances -+ TypeSynonymInstances -+ TypeOperators -+ FunctionalDependencies -+ MultiParamTypeClasses -+ -+ Ghc-Options: -Wall -+ -+ if impl(ghc) -+ Cpp-Options: -DCOMPILER_GHC -+ -+Executable test-framework-tests -+ Main-Is: Test/Framework/Tests.hs -+ -+ if !flag(tests) -+ Buildable: False -+ else -+ Build-Depends: HUnit >= 1.2, QuickCheck >= 2.3 && < 2.5, -+ base >= 4.3 && < 5, random >= 1.0, containers >= 0.1, -+ ansi-terminal >= 0.4.0, ansi-wl-pprint >= 0.5.1, -+ regex-posix >= 0.72, -+ old-locale >= 1.0, time >= 1.1.2, -+ xml >= 1.3.5, hostname >= 1.0, -+ libxml >= 0.1.1, bytestring >= 0.9 -+ -+ Extensions: CPP -+ PatternGuards -+ ExistentialQuantification -+ RecursiveDo -+ FlexibleInstances -+ TypeSynonymInstances -+ TypeOperators -+ FunctionalDependencies -+ MultiParamTypeClasses -+ -+ Cpp-Options: -DTEST -+ -+ Ghc-Options: -Wall -threaded -+ -+ if impl(ghc) -+ Cpp-Options: -DCOMPILER_GHC -+ -+Source-Repository head -+ Type: git -+ Location: https://github.com/haskell/test-framework diff --git a/patches/text-1.2.2.2.patch b/patches/text-1.2.2.2.patch deleted file mode 100644 index e5de5ae46c75aa0b2612504476d38b72cc09a11c..0000000000000000000000000000000000000000 --- a/patches/text-1.2.2.2.patch +++ /dev/null @@ -1,37 +0,0 @@ -diff --git a/Data/Text/Lazy/Builder/Int.hs b/Data/Text/Lazy/Builder/Int.hs -index e096f19..2a41538 100644 ---- a/Data/Text/Lazy/Builder/Int.hs -+++ b/Data/Text/Lazy/Builder/Int.hs -@@ -1,5 +1,5 @@ - {-# LANGUAGE BangPatterns, CPP, MagicHash, RankNTypes, ScopedTypeVariables, -- UnboxedTuples #-} -+ UnboxedTuples, NoImplicitPrelude #-} - #if __GLASGOW_HASKELL__ >= 702 - {-# LANGUAGE Trustworthy #-} - #endif -@@ -32,6 +32,7 @@ import GHC.Base (quotInt, remInt) - import GHC.Num (quotRemInteger) - import GHC.Types (Int(..)) - import Control.Monad.ST -+import Prelude hiding ((<>)) - - #ifdef __GLASGOW_HASKELL__ - # if defined(INTEGER_GMP) -diff --git a/Data/Text/Lazy/Builder/RealFloat.hs b/Data/Text/Lazy/Builder/RealFloat.hs -index 22141cd..720c07e 100644 ---- a/Data/Text/Lazy/Builder/RealFloat.hs -+++ b/Data/Text/Lazy/Builder/RealFloat.hs -@@ -1,4 +1,4 @@ --{-# LANGUAGE CPP, OverloadedStrings #-} -+{-# LANGUAGE CPP, OverloadedStrings, NoImplicitPrelude #-} - #if __GLASGOW_HASKELL__ >= 702 - {-# LANGUAGE Trustworthy #-} - #endif -@@ -24,6 +24,7 @@ import Data.Text.Lazy.Builder.Int (decimal) - import Data.Text.Internal.Builder.RealFloat.Functions (roundTo) - import Data.Text.Lazy.Builder - import qualified Data.Text as T -+import Prelude hiding ((<>)) - - -- | Control the rendering of floating point numbers. - data FPFormat = Exponent diff --git a/patches/th-desugar-1.7.patch b/patches/th-desugar-1.7.patch deleted file mode 100644 index 11e9f774a3049d1d60050abf8fa8da54d014e190..0000000000000000000000000000000000000000 --- a/patches/th-desugar-1.7.patch +++ /dev/null @@ -1,13 +0,0 @@ -diff -ru th-desugar-1.7.orig/Language/Haskell/TH/Desugar/Reify.hs th-desugar-1.7/Language/Haskell/TH/Desugar/Reify.hs ---- th-desugar-1.7.orig/Language/Haskell/TH/Desugar/Reify.hs 2017-06-01 13:21:00.000000000 -0400 -+++ th-desugar-1.7/Language/Haskell/TH/Desugar/Reify.hs 2017-11-09 08:59:07.185824504 -0500 -@@ -167,6 +167,9 @@ - #if __GLASGOW_HASKELL__ >= 800 - , Fail.MonadFail - #endif -+#if __GLASGOW_HASKELL__ >= 803 -+ , MonadIO -+#endif - ) - - instance Quasi q => DsMonad (DsM q) where diff --git a/patches/th-expand-syns-0.4.3.0.patch b/patches/th-expand-syns-0.4.3.0.patch deleted file mode 100644 index 1454a0173f5b6ce5efc61f3cd5c5bd85151ec71e..0000000000000000000000000000000000000000 --- a/patches/th-expand-syns-0.4.3.0.patch +++ /dev/null @@ -1,27 +0,0 @@ -diff -ru th-expand-syns-0.4.3.0.orig/Language/Haskell/TH/ExpandSyns.hs th-expand-syns-0.4.3.0/Language/Haskell/TH/ExpandSyns.hs ---- th-expand-syns-0.4.3.0.orig/Language/Haskell/TH/ExpandSyns.hs 2017-04-21 02:05:11.000000000 +0200 -+++ th-expand-syns-0.4.3.0/Language/Haskell/TH/ExpandSyns.hs 2017-09-17 12:32:12.476427680 +0200 -@@ -17,6 +17,7 @@ - import Data.Generics - import Control.Monad - import Data.Monoid -+import Data.Semigroup - import Prelude - - -- For ghci -@@ -91,9 +92,13 @@ - sesWarnTypeFamilies = True - } - -- mappend (SynonymExpansionSettings w1) (SynonymExpansionSettings w2) = -+ mappend = (<>) -+ -+instance Semigroup SynonymExpansionSettings where -+ (SynonymExpansionSettings w1) <> (SynonymExpansionSettings w2) = - SynonymExpansionSettings (w1 && w2) - -+ - -- | Suppresses the warning that type families are unsupported. - noWarnTypeFamilies :: SynonymExpansionSettings - noWarnTypeFamilies = mempty { sesWarnTypeFamilies = False } -Only in th-expand-syns-0.4.3.0/Language/Haskell/TH: ExpandSyns.hs~ diff --git a/patches/th-orphans-0.13.5.patch b/patches/th-orphans-0.13.5.patch deleted file mode 100644 index 27237dfa1c07c10ef946a32f069fd05031156980..0000000000000000000000000000000000000000 --- a/patches/th-orphans-0.13.5.patch +++ /dev/null @@ -1,266 +0,0 @@ -commit 3fa80a7a4c7e2af4d1ddaeab367068a6456028f9 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Tue Apr 3 14:44:43 2018 -0400 - - Fix the build with template-haskell-2.14 - -diff --git a/src/Language/Haskell/TH/Instances.hs b/src/Language/Haskell/TH/Instances.hs -index ca0796c..bd4d85b 100644 ---- a/src/Language/Haskell/TH/Instances.hs -+++ b/src/Language/Haskell/TH/Instances.hs -@@ -356,147 +356,159 @@ instance Applicative PprM where - #endif - - instance Quasi m => Quasi (ReaderT r m) where -- qNewName = MTL.lift . qNewName -- qReport a b = MTL.lift $ qReport a b -- qRecover m1 m2 = ReaderT $ \ r -> runReaderT m1 r `qRecover` runReaderT m2 r -- qReify = MTL.lift . qReify -- qLocation = MTL.lift qLocation -- qRunIO = MTL.lift . qRunIO -+ qNewName = MTL.lift . qNewName -+ qReport a b = MTL.lift $ qReport a b -+ qRecover m1 m2 = ReaderT $ \ r -> runReaderT m1 r `qRecover` runReaderT m2 r -+ qReify = MTL.lift . qReify -+ qLocation = MTL.lift qLocation -+ qRunIO = MTL.lift . qRunIO - #if MIN_VERSION_template_haskell(2,7,0) -- qReifyInstances a b = MTL.lift $ qReifyInstances a b -- qLookupName a b = MTL.lift $ qLookupName a b -- qAddDependentFile = MTL.lift . qAddDependentFile -+ qReifyInstances a b = MTL.lift $ qReifyInstances a b -+ qLookupName a b = MTL.lift $ qLookupName a b -+ qAddDependentFile = MTL.lift . qAddDependentFile - # if MIN_VERSION_template_haskell(2,9,0) -- qReifyRoles = MTL.lift . qReifyRoles -- qReifyAnnotations = MTL.lift . qReifyAnnotations -- qReifyModule = MTL.lift . qReifyModule -- qAddTopDecls = MTL.lift . qAddTopDecls -- qAddModFinalizer = MTL.lift . qAddModFinalizer -- qGetQ = MTL.lift qGetQ -- qPutQ = MTL.lift . qPutQ -+ qReifyRoles = MTL.lift . qReifyRoles -+ qReifyAnnotations = MTL.lift . qReifyAnnotations -+ qReifyModule = MTL.lift . qReifyModule -+ qAddTopDecls = MTL.lift . qAddTopDecls -+ qAddModFinalizer = MTL.lift . qAddModFinalizer -+ qGetQ = MTL.lift qGetQ -+ qPutQ = MTL.lift . qPutQ - # endif - # if MIN_VERSION_template_haskell(2,11,0) -- qReifyFixity = MTL.lift . qReifyFixity -- qReifyConStrictness = MTL.lift . qReifyConStrictness -- qIsExtEnabled = MTL.lift . qIsExtEnabled -- qExtsEnabled = MTL.lift qExtsEnabled -+ qReifyFixity = MTL.lift . qReifyFixity -+ qReifyConStrictness = MTL.lift . qReifyConStrictness -+ qIsExtEnabled = MTL.lift . qIsExtEnabled -+ qExtsEnabled = MTL.lift qExtsEnabled - # endif - #elif MIN_VERSION_template_haskell(2,5,0) -- qClassInstances a b = MTL.lift $ qClassInstances a b -+ qClassInstances a b = MTL.lift $ qClassInstances a b - #endif --#if MIN_VERSION_template_haskell(2,12,0) -- qAddForeignFile a b = MTL.lift $ qAddForeignFile a b -+#if MIN_VERSION_template_haskell(2,14,0) -+ qAddForeignFilePath a b = MTL.lift $ qAddForeignFilePath a b -+ qAddTempFile = MTL.lift . qAddTempFile -+#elif MIN_VERSION_template_haskell(2,12,0) -+ qAddForeignFile a b = MTL.lift $ qAddForeignFile a b - #endif - #if MIN_VERSION_template_haskell(2,13,0) -- qAddCorePlugin = MTL.lift . qAddCorePlugin -+ qAddCorePlugin = MTL.lift . qAddCorePlugin - #endif - - instance (Quasi m, Monoid w) => Quasi (WriterT w m) where -- qNewName = MTL.lift . qNewName -- qReport a b = MTL.lift $ qReport a b -- qRecover m1 m2 = WriterT $ runWriterT m1 `qRecover` runWriterT m2 -- qReify = MTL.lift . qReify -- qLocation = MTL.lift qLocation -- qRunIO = MTL.lift . qRunIO -+ qNewName = MTL.lift . qNewName -+ qReport a b = MTL.lift $ qReport a b -+ qRecover m1 m2 = WriterT $ runWriterT m1 `qRecover` runWriterT m2 -+ qReify = MTL.lift . qReify -+ qLocation = MTL.lift qLocation -+ qRunIO = MTL.lift . qRunIO - #if MIN_VERSION_template_haskell(2,7,0) -- qReifyInstances a b = MTL.lift $ qReifyInstances a b -- qLookupName a b = MTL.lift $ qLookupName a b -- qAddDependentFile = MTL.lift . qAddDependentFile -+ qReifyInstances a b = MTL.lift $ qReifyInstances a b -+ qLookupName a b = MTL.lift $ qLookupName a b -+ qAddDependentFile = MTL.lift . qAddDependentFile - # if MIN_VERSION_template_haskell(2,9,0) -- qReifyRoles = MTL.lift . qReifyRoles -- qReifyAnnotations = MTL.lift . qReifyAnnotations -- qReifyModule = MTL.lift . qReifyModule -- qAddTopDecls = MTL.lift . qAddTopDecls -- qAddModFinalizer = MTL.lift . qAddModFinalizer -- qGetQ = MTL.lift qGetQ -- qPutQ = MTL.lift . qPutQ -+ qReifyRoles = MTL.lift . qReifyRoles -+ qReifyAnnotations = MTL.lift . qReifyAnnotations -+ qReifyModule = MTL.lift . qReifyModule -+ qAddTopDecls = MTL.lift . qAddTopDecls -+ qAddModFinalizer = MTL.lift . qAddModFinalizer -+ qGetQ = MTL.lift qGetQ -+ qPutQ = MTL.lift . qPutQ - # endif - # if MIN_VERSION_template_haskell(2,11,0) -- qReifyFixity = MTL.lift . qReifyFixity -- qReifyConStrictness = MTL.lift . qReifyConStrictness -- qIsExtEnabled = MTL.lift . qIsExtEnabled -- qExtsEnabled = MTL.lift qExtsEnabled -+ qReifyFixity = MTL.lift . qReifyFixity -+ qReifyConStrictness = MTL.lift . qReifyConStrictness -+ qIsExtEnabled = MTL.lift . qIsExtEnabled -+ qExtsEnabled = MTL.lift qExtsEnabled - # endif - #elif MIN_VERSION_template_haskell(2,5,0) -- qClassInstances a b = MTL.lift $ qClassInstances a b -+ qClassInstances a b = MTL.lift $ qClassInstances a b - #endif --#if MIN_VERSION_template_haskell(2,12,0) -- qAddForeignFile a b = MTL.lift $ qAddForeignFile a b -+#if MIN_VERSION_template_haskell(2,14,0) -+ qAddForeignFilePath a b = MTL.lift $ qAddForeignFilePath a b -+ qAddTempFile = MTL.lift . qAddTempFile -+#elif MIN_VERSION_template_haskell(2,12,0) -+ qAddForeignFile a b = MTL.lift $ qAddForeignFile a b - #endif - #if MIN_VERSION_template_haskell(2,13,0) -- qAddCorePlugin = MTL.lift . qAddCorePlugin -+ qAddCorePlugin = MTL.lift . qAddCorePlugin - #endif - - instance Quasi m => Quasi (StateT s m) where -- qNewName = MTL.lift . qNewName -- qReport a b = MTL.lift $ qReport a b -- qRecover m1 m2 = StateT $ \ s -> runStateT m1 s `qRecover` runStateT m2 s -- qReify = MTL.lift . qReify -- qLocation = MTL.lift qLocation -- qRunIO = MTL.lift . qRunIO -+ qNewName = MTL.lift . qNewName -+ qReport a b = MTL.lift $ qReport a b -+ qRecover m1 m2 = StateT $ \ s -> runStateT m1 s `qRecover` runStateT m2 s -+ qReify = MTL.lift . qReify -+ qLocation = MTL.lift qLocation -+ qRunIO = MTL.lift . qRunIO - #if MIN_VERSION_template_haskell(2,7,0) -- qReifyInstances a b = MTL.lift $ qReifyInstances a b -- qLookupName a b = MTL.lift $ qLookupName a b -- qAddDependentFile = MTL.lift . qAddDependentFile -+ qReifyInstances a b = MTL.lift $ qReifyInstances a b -+ qLookupName a b = MTL.lift $ qLookupName a b -+ qAddDependentFile = MTL.lift . qAddDependentFile - # if MIN_VERSION_template_haskell(2,9,0) -- qReifyRoles = MTL.lift . qReifyRoles -- qReifyAnnotations = MTL.lift . qReifyAnnotations -- qReifyModule = MTL.lift . qReifyModule -- qAddTopDecls = MTL.lift . qAddTopDecls -- qAddModFinalizer = MTL.lift . qAddModFinalizer -- qGetQ = MTL.lift qGetQ -- qPutQ = MTL.lift . qPutQ -+ qReifyRoles = MTL.lift . qReifyRoles -+ qReifyAnnotations = MTL.lift . qReifyAnnotations -+ qReifyModule = MTL.lift . qReifyModule -+ qAddTopDecls = MTL.lift . qAddTopDecls -+ qAddModFinalizer = MTL.lift . qAddModFinalizer -+ qGetQ = MTL.lift qGetQ -+ qPutQ = MTL.lift . qPutQ - # endif - # if MIN_VERSION_template_haskell(2,11,0) -- qReifyFixity = MTL.lift . qReifyFixity -- qReifyConStrictness = MTL.lift . qReifyConStrictness -- qIsExtEnabled = MTL.lift . qIsExtEnabled -- qExtsEnabled = MTL.lift qExtsEnabled -+ qReifyFixity = MTL.lift . qReifyFixity -+ qReifyConStrictness = MTL.lift . qReifyConStrictness -+ qIsExtEnabled = MTL.lift . qIsExtEnabled -+ qExtsEnabled = MTL.lift qExtsEnabled - # endif - #elif MIN_VERSION_template_haskell(2,5,0) -- qClassInstances a b = MTL.lift $ qClassInstances a b -+ qClassInstances a b = MTL.lift $ qClassInstances a b - #endif --#if MIN_VERSION_template_haskell(2,12,0) -- qAddForeignFile a b = MTL.lift $ qAddForeignFile a b -+#if MIN_VERSION_template_haskell(2,14,0) -+ qAddForeignFilePath a b = MTL.lift $ qAddForeignFilePath a b -+ qAddTempFile = MTL.lift . qAddTempFile -+#elif MIN_VERSION_template_haskell(2,12,0) -+ qAddForeignFile a b = MTL.lift $ qAddForeignFile a b - #endif - #if MIN_VERSION_template_haskell(2,13,0) -- qAddCorePlugin = MTL.lift . qAddCorePlugin -+ qAddCorePlugin = MTL.lift . qAddCorePlugin - #endif - - instance (Quasi m, Monoid w) => Quasi (RWST r w s m) where -- qNewName = MTL.lift . qNewName -- qReport a b = MTL.lift $ qReport a b -- qRecover m1 m2 = RWST $ \ r s -> runRWST m1 r s `qRecover` runRWST m2 r s -- qReify = MTL.lift . qReify -- qLocation = MTL.lift qLocation -- qRunIO = MTL.lift . qRunIO -+ qNewName = MTL.lift . qNewName -+ qReport a b = MTL.lift $ qReport a b -+ qRecover m1 m2 = RWST $ \ r s -> runRWST m1 r s `qRecover` runRWST m2 r s -+ qReify = MTL.lift . qReify -+ qLocation = MTL.lift qLocation -+ qRunIO = MTL.lift . qRunIO - #if MIN_VERSION_template_haskell(2,7,0) -- qReifyInstances a b = MTL.lift $ qReifyInstances a b -- qLookupName a b = MTL.lift $ qLookupName a b -- qAddDependentFile = MTL.lift . qAddDependentFile -+ qReifyInstances a b = MTL.lift $ qReifyInstances a b -+ qLookupName a b = MTL.lift $ qLookupName a b -+ qAddDependentFile = MTL.lift . qAddDependentFile - # if MIN_VERSION_template_haskell(2,9,0) -- qReifyRoles = MTL.lift . qReifyRoles -- qReifyAnnotations = MTL.lift . qReifyAnnotations -- qReifyModule = MTL.lift . qReifyModule -- qAddTopDecls = MTL.lift . qAddTopDecls -- qAddModFinalizer = MTL.lift . qAddModFinalizer -- qGetQ = MTL.lift qGetQ -- qPutQ = MTL.lift . qPutQ -+ qReifyRoles = MTL.lift . qReifyRoles -+ qReifyAnnotations = MTL.lift . qReifyAnnotations -+ qReifyModule = MTL.lift . qReifyModule -+ qAddTopDecls = MTL.lift . qAddTopDecls -+ qAddModFinalizer = MTL.lift . qAddModFinalizer -+ qGetQ = MTL.lift qGetQ -+ qPutQ = MTL.lift . qPutQ - # endif - # if MIN_VERSION_template_haskell(2,11,0) -- qReifyFixity = MTL.lift . qReifyFixity -- qReifyConStrictness = MTL.lift . qReifyConStrictness -- qIsExtEnabled = MTL.lift . qIsExtEnabled -- qExtsEnabled = MTL.lift qExtsEnabled -+ qReifyFixity = MTL.lift . qReifyFixity -+ qReifyConStrictness = MTL.lift . qReifyConStrictness -+ qIsExtEnabled = MTL.lift . qIsExtEnabled -+ qExtsEnabled = MTL.lift qExtsEnabled - # endif - #elif MIN_VERSION_template_haskell(2,5,0) -- qClassInstances a b = MTL.lift $ qClassInstances a b -+ qClassInstances a b = MTL.lift $ qClassInstances a b - #endif --#if MIN_VERSION_template_haskell(2,12,0) -- qAddForeignFile a b = MTL.lift $ qAddForeignFile a b -+#if MIN_VERSION_template_haskell(2,14,0) -+ qAddForeignFilePath a b = MTL.lift $ qAddForeignFilePath a b -+ qAddTempFile = MTL.lift . qAddTempFile -+#elif MIN_VERSION_template_haskell(2,12,0) -+ qAddForeignFile a b = MTL.lift $ qAddForeignFile a b - #endif - #if MIN_VERSION_template_haskell(2,13,0) -- qAddCorePlugin = MTL.lift . qAddCorePlugin -+ qAddCorePlugin = MTL.lift . qAddCorePlugin - #endif - - #if MIN_VERSION_base(4,7,0) && defined(LANGUAGE_DeriveDataTypeable) && __GLASGOW_HASKELL__ < 710 diff --git a/patches/tls-1.4.0.patch b/patches/tls-1.4.0.patch deleted file mode 100644 index 9bfe0879239a5c2e3a6fcc53bcc38115f8ceddd6..0000000000000000000000000000000000000000 --- a/patches/tls-1.4.0.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ru tls-1.4.0.orig/Network/TLS/Credentials.hs tls-1.4.0/Network/TLS/Credentials.hs ---- tls-1.4.0.orig/Network/TLS/Credentials.hs 2017-07-31 20:31:58.000000000 +0200 -+++ tls-1.4.0/Network/TLS/Credentials.hs 2017-09-15 12:19:46.218278360 +0200 -@@ -21,6 +21,7 @@ - - import Data.ByteString (ByteString) - import Data.Monoid -+import Data.Semigroup - import Data.Maybe (catMaybes) - import Data.List (find) - import Network.TLS.Crypto -@@ -36,9 +37,12 @@ - - newtype Credentials = Credentials [Credential] - -+instance Semigroup Credentials where -+ (Credentials l1) <> (Credentials l2) = Credentials (l1 ++ l2) -+ - instance Monoid Credentials where - mempty = Credentials [] -- mappend (Credentials l1) (Credentials l2) = Credentials (l1 ++ l2) -+ mappend = (<>) - - -- | try to create a new credential object from a public certificate - -- and the associated private key that are stored on the filesystem -Only in tls-1.4.0/Network/TLS: Credentials.hs~ diff --git a/patches/turtle-1.4.3.patch b/patches/turtle-1.4.3.patch deleted file mode 100644 index 05e273b264370b702086d5fa834a8402c6e61a10..0000000000000000000000000000000000000000 --- a/patches/turtle-1.4.3.patch +++ /dev/null @@ -1,57 +0,0 @@ -diff -ru turtle-1.4.3.orig/src/Turtle/Line.hs turtle-1.4.3/src/Turtle/Line.hs ---- turtle-1.4.3.orig/src/Turtle/Line.hs 2017-09-03 05:32:33.000000000 +0200 -+++ turtle-1.4.3/src/Turtle/Line.hs 2017-09-14 22:42:12.429258366 +0200 -@@ -60,7 +60,7 @@ - - -- | A line of text (does not contain newlines). - newtype Line = Line Text -- deriving (Eq, Ord, Show, Monoid) -+ deriving (Eq, Ord, Show, Semigroup, Monoid) - - instance IsString Line where - fromString = fromMaybe (throw NewlineForbidden) . textToLine . fromString -Only in turtle-1.4.3/src/Turtle: Line.hs~ -diff -ru turtle-1.4.3.orig/src/Turtle/Pattern.hs turtle-1.4.3/src/Turtle/Pattern.hs ---- turtle-1.4.3.orig/src/Turtle/Pattern.hs 2017-09-03 05:32:33.000000000 +0200 -+++ turtle-1.4.3/src/Turtle/Pattern.hs 2017-09-14 22:43:00.097008668 +0200 -@@ -114,6 +114,7 @@ - import Data.Char - import Data.List (foldl') - import Data.Monoid -+import Data.Semigroup (Semigroup(..)) - import Data.String (IsString(..)) - import Data.Text (Text) - import qualified Data.Text as Text -@@ -123,6 +124,9 @@ - newtype Pattern a = Pattern { runPattern :: StateT Text [] a } - deriving (Functor, Applicative, Monad, Alternative, MonadPlus) - -+instance Monoid a => Semigroup (Pattern a) where -+ (<>) = liftA2 mappend -+ - instance Monoid a => Monoid (Pattern a) where - mempty = pure mempty - mappend = liftA2 mappend -Only in turtle-1.4.3/src/Turtle: Pattern.hs~ -diff -ru turtle-1.4.3.orig/src/Turtle/Shell.hs turtle-1.4.3/src/Turtle/Shell.hs ---- turtle-1.4.3.orig/src/Turtle/Shell.hs 2017-09-03 05:32:33.000000000 +0200 -+++ turtle-1.4.3/src/Turtle/Shell.hs 2017-09-14 22:43:54.392724014 +0200 -@@ -82,6 +82,7 @@ - import Data.Foldable (Foldable) - import qualified Data.Foldable - import Data.Monoid -+import Data.Semigroup (Semigroup(..)) - import Data.String (IsString(..)) - import Prelude -- Fix redundant import warnings - -@@ -159,6 +160,9 @@ - fail = Prelude.fail - #endif - -+instance Monoid a => Semigroup (Shell a) where -+ (<>) = liftA2 mappend -+ - instance Monoid a => Monoid (Shell a) where - mempty = pure mempty - mappend = liftA2 mappend -Only in turtle-1.4.3/src/Turtle: Shell.hs~ diff --git a/patches/unordered-containers-0.2.8.0.patch b/patches/unordered-containers-0.2.8.0.patch deleted file mode 100644 index 2a9f938aad38455fa7aa215ec373a9094bcd21d1..0000000000000000000000000000000000000000 --- a/patches/unordered-containers-0.2.8.0.patch +++ /dev/null @@ -1,27 +0,0 @@ -From ef0f5a1e6fec6e1f126fc69c63c66b0cff6d88d0 Mon Sep 17 00:00:00 2001 -From: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Fri, 8 Sep 2017 20:04:05 -0400 -Subject: [PATCH] =?UTF-8?q?Fix=20the=20build=20post-Semigroup=E2=80=93Mono?= - =?UTF-8?q?id=20Proposal?= -MIME-Version: 1.0 -Content-Type: text/plain; charset=UTF-8 -Content-Transfer-Encoding: 8bit - ---- - Data/HashSet.hs | 2 +- - utils/Stats.hs | 14 ++++++++++---- - 2 files changed, 11 insertions(+), 5 deletions(-) - -diff --git a/Data/HashSet.hs b/Data/HashSet.hs -index ba7200b..ac40cbd 100644 ---- a/Data/HashSet.hs -+++ b/Data/HashSet.hs -@@ -77,7 +77,7 @@ import Data.Data hiding (Typeable) - import Data.HashMap.Base (HashMap, foldrWithKey, equalKeys) - import Data.Hashable (Hashable(hashWithSalt)) - #if __GLASGOW_HASKELL__ >= 711 --import Data.Semigroup (Semigroup(..), Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - #elif __GLASGOW_HASKELL__ < 709 - import Data.Monoid (Monoid(..)) - #endif diff --git a/patches/uri-bytestring-0.2.3.3.patch b/patches/uri-bytestring-0.2.3.3.patch deleted file mode 100644 index cd8e0c74ec9a8509e609aaab0c3fd13de8efff47..0000000000000000000000000000000000000000 --- a/patches/uri-bytestring-0.2.3.3.patch +++ /dev/null @@ -1,35 +0,0 @@ -diff -ru uri-bytestring-0.2.3.3.orig/src/URI/ByteString/Internal.hs uri-bytestring-0.2.3.3/src/URI/ByteString/Internal.hs ---- uri-bytestring-0.2.3.3.orig/src/URI/ByteString/Internal.hs 2017-06-06 17:27:21.000000000 +0200 -+++ uri-bytestring-0.2.3.3/src/URI/ByteString/Internal.hs 2017-09-15 11:50:19.212228883 +0200 -@@ -791,6 +791,7 @@ - , Alternative - , Monad - , MonadPlus -+ , Semigroup - , Monoid) - - -Only in uri-bytestring-0.2.3.3/src/URI/ByteString: Internal.hs~ -diff -ru uri-bytestring-0.2.3.3.orig/src/URI/ByteString/Types.hs uri-bytestring-0.2.3.3/src/URI/ByteString/Types.hs ---- uri-bytestring-0.2.3.3.orig/src/URI/ByteString/Types.hs 2017-06-06 17:27:21.000000000 +0200 -+++ uri-bytestring-0.2.3.3/src/URI/ByteString/Types.hs 2017-09-15 11:50:08.632288724 +0200 -@@ -15,6 +15,9 @@ - import Data.ByteString (ByteString) - import qualified Data.Map.Strict as M - import Data.Monoid -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup -+#endif - import Data.Typeable - import Data.Word - import GHC.Generics -@@ -89,7 +92,7 @@ - - ------------------------------------------------------------------------------- - newtype Query = Query { queryPairs :: [(ByteString, ByteString)] } -- deriving (Show, Eq, Monoid, Generic, Typeable, Ord) -+ deriving (Show, Eq, Semigroup, Monoid, Generic, Typeable, Ord) - - #ifdef LIFT_COMPAT - deriveLift ''Query -Only in uri-bytestring-0.2.3.3/src/URI/ByteString: Types.hs~ diff --git a/patches/uri-bytestring-0.3.0.2.patch b/patches/uri-bytestring-0.3.0.2.patch deleted file mode 100644 index d5c5b006917b9666b11797a49f160622897a8184..0000000000000000000000000000000000000000 --- a/patches/uri-bytestring-0.3.0.2.patch +++ /dev/null @@ -1,62 +0,0 @@ -diff --git a/src/URI/ByteString/Internal.hs b/src/URI/ByteString/Internal.hs -index c3a93d5..4c64740 100644 ---- a/src/URI/ByteString/Internal.hs -+++ b/src/URI/ByteString/Internal.hs -@@ -27,6 +27,7 @@ import Data.List (delete, intersperse, - import qualified Data.Map.Strict as M - import Data.Maybe - import Data.Monoid -+import Data.Semigroup (Semigroup) - import Data.Ord (comparing) - import Data.Word - import Text.Read (readMaybe) -@@ -794,6 +795,7 @@ newtype Parser' e a = Parser' { unParser' :: Parser a} - , Alternative - , Monad - , MonadPlus -+ , Semigroup - , Monoid) - - -diff --git a/src/URI/ByteString/Types.hs b/src/URI/ByteString/Types.hs -index 11f69d9..03fc683 100644 ---- a/src/URI/ByteString/Types.hs -+++ b/src/URI/ByteString/Types.hs -@@ -15,6 +15,7 @@ module URI.ByteString.Types where - import Data.ByteString (ByteString) - import qualified Data.Map.Strict as M - import Data.Monoid -+import Data.Semigroup (Semigroup) - import Data.Typeable - import Data.Word - import GHC.Generics -@@ -89,7 +90,7 @@ deriving instance Lift Authority - - ------------------------------------------------------------------------------- - newtype Query = Query { queryPairs :: [(ByteString, ByteString)] } -- deriving (Show, Eq, Monoid, Generic, Typeable, Ord) -+ deriving (Show, Eq, Semigroup, Monoid, Generic, Typeable, Ord) - - #ifdef LIFT_COMPAT - deriveLift ''Query -diff --git a/uri-bytestring.cabal b/uri-bytestring.cabal -index 316828c..133a178 100644 ---- a/uri-bytestring.cabal -+++ b/uri-bytestring.cabal -@@ -54,10 +54,11 @@ library - if impl(ghc >= 7.8) - cpp-options: -DWITH_TYPEABLE - -- if impl(ghc < 8) -+ if !impl(ghc >= 8) - cpp-options: -DLIFT_COMPAT - build-depends: -- th-lift >= 0.7.5 && < 0.8 -+ th-lift >= 0.7.5 && < 0.8, -+ semigroups >= 0.16.2.2 && <0.19 - - if flag(lib-Werror) - ghc-options: -Werror --- -2.7.4 - diff --git a/patches/vault-0.3.0.7.patch b/patches/vault-0.3.0.7.patch deleted file mode 100644 index 009466faf36315b4f94d4ad1f92164f9b29d48b7..0000000000000000000000000000000000000000 --- a/patches/vault-0.3.0.7.patch +++ /dev/null @@ -1,27 +0,0 @@ -Only in vault-0.3.0.7/src/Data/Unique: Really.hs~ -diff -ru vault-0.3.0.7.orig/src/Data/Vault/ST/ST.hs vault-0.3.0.7/src/Data/Vault/ST/ST.hs ---- vault-0.3.0.7.orig/src/Data/Vault/ST/ST.hs 2017-04-17 21:50:09.000000000 +0200 -+++ vault-0.3.0.7/src/Data/Vault/ST/ST.hs 2017-09-14 22:59:30.203780595 +0200 -@@ -13,6 +13,7 @@ - ) where - - import Data.Monoid (Monoid(..)) -+import Data.Semigroup (Semigroup(..)) - import Prelude hiding (lookup) - import Control.Applicative hiding (empty) - import Control.Monad.ST -@@ -38,9 +39,12 @@ - Vault - ------------------------------------------------------------------------------} - -+instance Semigroup (Vault s) where -+ (<>) = union -+ - instance Monoid (Vault s) where - mempty = empty -- mappend = union -+ mappend = (<>) - - -- | The empty vault. - empty :: Vault s -Only in vault-0.3.0.7/src/Data/Vault/ST: ST.hs~ diff --git a/patches/vector-space-0.12.patch b/patches/vector-space-0.12.patch deleted file mode 100644 index 50ac70caa9736782dd6bf759f152129fb4d9d075..0000000000000000000000000000000000000000 --- a/patches/vector-space-0.12.patch +++ /dev/null @@ -1,51 +0,0 @@ -commit 8c7d851513efbc814a0c5330d1e5e327f5fea935 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Thu Jan 25 12:29:25 2018 -0500 - - Add a Semigroup instance for Sum - -diff --git a/src/Data/AdditiveGroup.hs b/src/Data/AdditiveGroup.hs -index b42dc7b..f2f3f43 100644 ---- a/src/Data/AdditiveGroup.hs -+++ b/src/Data/AdditiveGroup.hs -@@ -31,6 +31,9 @@ import Data.Foldable (Foldable) - import Data.Foldable (foldr) - import Data.Complex hiding (magnitude) - import Data.Ratio -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - import Foreign.C.Types (CSChar, CInt, CShort, CLong, CLLong, CIntMax, CFloat, CDouble) - - import Data.MemoTrie -@@ -187,10 +190,14 @@ instance Applicative Sum where - pure = Sum - (<*>) = inSum2 ($) - -+instance AdditiveGroup a => Semigroup (Sum a) where -+ (<>) = liftA2 (^+^) -+ - instance AdditiveGroup a => Monoid (Sum a) where - mempty = Sum zeroV -- mappend = liftA2 (^+^) -- -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - -- | Application a unary function inside a 'Sum' - inSum :: (a -> b) -> (Sum a -> Sum b) -diff --git a/vector-space.cabal b/vector-space.cabal -index 84ee45c..af64d44 100644 ---- a/vector-space.cabal -+++ b/vector-space.cabal -@@ -55,6 +55,9 @@ Library - if !impl(ghc >= 7.9) { - Build-Depends: void >= 0.4 - } -+ if !impl(ghc >= 8.0) { -+ Build-Depends: semigroups >= 0.16 -+ } - ghc-options: -Wall -O2 - -- ghc-prof-options: -prof -auto-all - diff --git a/patches/vector-space-0.13.patch b/patches/vector-space-0.13.patch deleted file mode 100644 index ff8bc72d628eb578f32936d21677e9e72eecd1a9..0000000000000000000000000000000000000000 --- a/patches/vector-space-0.13.patch +++ /dev/null @@ -1,10 +0,0 @@ -diff -ru vector-space-0.13.orig/src/Data/Cross.hs vector-space-0.13/src/Data/Cross.hs ---- vector-space-0.13.orig/src/Data/Cross.hs 2018-01-25 15:08:37.000000000 -0500 -+++ vector-space-0.13/src/Data/Cross.hs 2018-07-09 11:31:01.810293273 -0400 -@@ -1,5 +1,5 @@ - {-# LANGUAGE FlexibleInstances, FlexibleContexts, TypeOperators -- , TypeFamilies, TypeSynonymInstances #-} -+ , TypeFamilies, TypeSynonymInstances, UndecidableInstances #-} - {-# OPTIONS_GHC -Wall #-} - ---------------------------------------------------------------------- - -- | diff --git a/patches/vinyl-0.7.0.patch b/patches/vinyl-0.7.0.patch deleted file mode 100644 index e10df2d20cffa2688f016cf4126890d3f0420536..0000000000000000000000000000000000000000 --- a/patches/vinyl-0.7.0.patch +++ /dev/null @@ -1,37 +0,0 @@ -diff --git a/Data/Vinyl/Core.hs b/Data/Vinyl/Core.hs -index 4400785..5d31570 100644 ---- a/Data/Vinyl/Core.hs -+++ b/Data/Vinyl/Core.hs -@@ -15,7 +15,8 @@ - - module Data.Vinyl.Core where - --import Data.Monoid -+import Data.Monoid hiding ((<>)) -+import Data.Semigroup - import Foreign.Ptr (castPtr, plusPtr) - import Foreign.Storable (Storable(..)) - import Data.Vinyl.Functor -@@ -226,13 +227,19 @@ instance RecAll f rs Show => Show (Rec f rs) where - . rmap (\(Compose (Dict x)) -> Const $ show x) - $ reifyConstraint (Proxy :: Proxy Show) xs - -+instance Semigroup (Rec f '[]) where -+ RNil <> RNil = RNil -+ -+instance (Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) where -+ (x :& xs) <> (y :& ys) = (x <> y) :& (xs <> ys) -+ - instance Monoid (Rec f '[]) where - mempty = RNil -- RNil `mappend` RNil = RNil -+ mappend = (<>) - --instance (Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) where -+instance (Semigroup (f r), Semigroup (Rec f rs), Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) where - mempty = mempty :& mempty -- (x :& xs) `mappend` (y :& ys) = (x <> y) :& (xs <> ys) -+ mappend = (<>) - - instance Eq (Rec f '[]) where - _ == _ = True diff --git a/patches/warp-3.2.23.patch b/patches/warp-3.2.23.patch deleted file mode 100644 index fba71d046b90b99b48f57207ce3f8b505a620ba5..0000000000000000000000000000000000000000 --- a/patches/warp-3.2.23.patch +++ /dev/null @@ -1,16 +0,0 @@ -diff -ru warp-3.2.23.orig/Network/Wai/Handler/Warp/FdCache.hs warp-3.2.23/Network/Wai/Handler/Warp/FdCache.hs ---- warp-3.2.23.orig/Network/Wai/Handler/Warp/FdCache.hs 2017-11-22 04:16:07.000000000 -0500 -+++ warp-3.2.23/Network/Wai/Handler/Warp/FdCache.hs 2018-07-15 07:41:10.495001048 -0400 -@@ -69,7 +69,11 @@ - - openFile :: FilePath -> IO Fd - openFile path = do -- fd <- openFd path ReadOnly Nothing defaultFileFlags{nonBlock=False} -+ fd <- openFd path ReadOnly -+#if !(MIN_VERSION_unix(2,8,0)) -+ Nothing -+#endif -+ defaultFileFlags{nonBlock=False} - setFileCloseOnExec fd - return fd - diff --git a/patches/websockets-0.12.3.1.patch b/patches/websockets-0.12.3.1.patch deleted file mode 100644 index 15d8c003cc8ea7d2cf94385322897b8df5683bdb..0000000000000000000000000000000000000000 --- a/patches/websockets-0.12.3.1.patch +++ /dev/null @@ -1,37 +0,0 @@ -From 11ba6d15cf47bace1936b13a58192e37908b0300 Mon Sep 17 00:00:00 2001 -From: Kosyrev Serge <serge.kosyrev@iohk.io> -Date: Sun, 14 Jan 2018 02:58:10 +0300 -Subject: [PATCH] Options.hs:SizeLimit: add Semigroup instance (GHC 8.4 - compat) - ---- - src/Network/WebSockets/Connection/Options.hs | 9 ++++++++- - 1 file changed, 8 insertions(+), 1 deletion(-) - -diff --git a/src/Network/WebSockets/Connection/Options.hs b/src/Network/WebSockets/Connection/Options.hs -index ae9b67f..1bf0168 100644 ---- a/src/Network/WebSockets/Connection/Options.hs -+++ b/src/Network/WebSockets/Connection/Options.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - -------------------------------------------------------------------------------- - module Network.WebSockets.Connection.Options - ( ConnectionOptions (..) -@@ -109,10 +110,16 @@ data SizeLimit - instance Monoid SizeLimit where - mempty = NoSizeLimit - -+#if !MIN_VERSION_base(4,11,0) - mappend NoSizeLimit y = y - mappend x NoSizeLimit = x - mappend (SizeLimit x) (SizeLimit y) = SizeLimit (min x y) -- -+#else -+instance Semigroup SizeLimit where -+ (<>) NoSizeLimit y = y -+ (<>) x NoSizeLimit = x -+ (<>) (SizeLimit x) (SizeLimit y) = SizeLimit (min x y) -+#endif - - -------------------------------------------------------------------------------- - atMostSizeLimit :: Int64 -> SizeLimit -> Bool diff --git a/patches/x509-1.7.2.patch b/patches/x509-1.7.2.patch deleted file mode 100644 index e3cae3783c4c724af5e4a0142627940a30a33c93..0000000000000000000000000000000000000000 --- a/patches/x509-1.7.2.patch +++ /dev/null @@ -1,159 +0,0 @@ -diff -ru x509-1.7.2.orig/Data/X509/DistinguishedName.hs x509-1.7.2/Data/X509/DistinguishedName.hs ---- x509-1.7.2.orig/Data/X509/DistinguishedName.hs 2017-06-26 18:12:09.000000000 +0200 -+++ x509-1.7.2/Data/X509/DistinguishedName.hs 2017-09-15 12:17:10.135154154 +0200 -@@ -17,6 +17,7 @@ - - import Control.Applicative - import Data.Monoid -+import Data.Semigroup - import Data.ASN1.Types - import Data.X509.Internal - -@@ -49,9 +50,12 @@ - newtype DistinguishedNameInner = DistinguishedNameInner DistinguishedName - deriving (Show,Eq) - -+instance Semigroup DistinguishedName where -+ (DistinguishedName l1) <> (DistinguishedName l2) = DistinguishedName (l1++l2) -+ - instance Monoid DistinguishedName where - mempty = DistinguishedName [] -- mappend (DistinguishedName l1) (DistinguishedName l2) = DistinguishedName (l1++l2) -+ mappend = (<>) - - instance ASN1Object DistinguishedName where - toASN1 dn = \xs -> encodeDN dn ++ xs -Only in x509-1.7.2/Data/X509: DistinguishedName.hs~ -diff -ru x509-1.7.2.orig/x509.cabal x509-1.7.2/x509.cabal ---- x509-1.7.2.orig/x509.cabal 2017-07-31 22:23:12.000000000 +0200 -+++ x509-1.7.2/x509.cabal 2017-09-15 12:16:16.747453563 +0200 -@@ -1,64 +1,65 @@ --Name: x509 --version: 1.7.2 --Description: X509 reader and writer --License: BSD3 --License-file: LICENSE --Copyright: Vincent Hanquez <vincent@snarc.org> --Author: Vincent Hanquez <vincent@snarc.org> --Maintainer: Vincent Hanquez <vincent@snarc.org> --Synopsis: X509 reader and writer --Build-Type: Simple --Category: Data --stability: experimental --Homepage: http://github.com/vincenthz/hs-certificate --Cabal-Version: >= 1.10 -- --Library -- Default-Language: Haskell2010 -- Build-Depends: base >= 3 && < 5 -- , bytestring -- , memory -- , mtl -- , containers -- , hourglass -- , pem >= 0.1 && < 0.3 -- , asn1-types >= 0.3.1 && < 0.4 -- , asn1-encoding >= 0.9 && < 0.10 -- , asn1-parse >= 0.9.3 && < 0.10 -- , cryptonite >= 0.8 -- Exposed-modules: Data.X509 -- Data.X509.EC -- Other-modules: Data.X509.Internal -- Data.X509.CertificateChain -- Data.X509.AlgorithmIdentifier -- Data.X509.DistinguishedName -- Data.X509.Cert -- Data.X509.PublicKey -- Data.X509.PrivateKey -- Data.X509.Ext -- Data.X509.ExtensionRaw -- Data.X509.CRL -- Data.X509.OID -- Data.X509.Signed -- ghc-options: -Wall -- --Test-Suite test-x509 -- Default-Language: Haskell2010 -- type: exitcode-stdio-1.0 -- hs-source-dirs: Tests -- Main-is: Tests.hs -- Build-Depends: base >= 3 && < 5 -- , bytestring -- , mtl -- , tasty -- , tasty-quickcheck -- , hourglass -- , asn1-types -- , x509 -- , cryptonite -- ghc-options: -Wall -fno-warn-orphans -fno-warn-missing-signatures -- --source-repository head -- type: git -- location: git://github.com/vincenthz/hs-certificate -- subdir: x509 -+Name: x509 -+version: 1.7.2 -+x-revision: 1 -+Description: X509 reader and writer -+License: BSD3 -+License-file: LICENSE -+Copyright: Vincent Hanquez <vincent@snarc.org> -+Author: Vincent Hanquez <vincent@snarc.org> -+Maintainer: Vincent Hanquez <vincent@snarc.org> -+Synopsis: X509 reader and writer -+Build-Type: Simple -+Category: Data -+stability: experimental -+Homepage: http://github.com/vincenthz/hs-certificate -+Cabal-Version: >= 1.10 -+ -+Library -+ Default-Language: Haskell2010 -+ Build-Depends: base >= 4.7 && < 5 -+ , bytestring -+ , memory -+ , mtl -+ , containers -+ , hourglass -+ , pem >= 0.1 && < 0.3 -+ , asn1-types >= 0.3.1 && < 0.4 -+ , asn1-encoding >= 0.9 && < 0.10 -+ , asn1-parse >= 0.9.3 && < 0.10 -+ , cryptonite >= 0.8 -+ Exposed-modules: Data.X509 -+ Data.X509.EC -+ Other-modules: Data.X509.Internal -+ Data.X509.CertificateChain -+ Data.X509.AlgorithmIdentifier -+ Data.X509.DistinguishedName -+ Data.X509.Cert -+ Data.X509.PublicKey -+ Data.X509.PrivateKey -+ Data.X509.Ext -+ Data.X509.ExtensionRaw -+ Data.X509.CRL -+ Data.X509.OID -+ Data.X509.Signed -+ ghc-options: -Wall -+ -+Test-Suite test-x509 -+ Default-Language: Haskell2010 -+ type: exitcode-stdio-1.0 -+ hs-source-dirs: Tests -+ Main-is: Tests.hs -+ Build-Depends: base >= 3 && < 5 -+ , bytestring -+ , mtl -+ , tasty -+ , tasty-quickcheck -+ , hourglass -+ , asn1-types -+ , x509 -+ , cryptonite -+ ghc-options: -Wall -fno-warn-orphans -fno-warn-missing-signatures -+ -+source-repository head -+ type: git -+ location: git://github.com/vincenthz/hs-certificate -+ subdir: x509 diff --git a/patches/x509-store-1.6.5.patch b/patches/x509-store-1.6.5.patch deleted file mode 100644 index 3e1550a09905423be6521a3ad371df5af7908daa..0000000000000000000000000000000000000000 --- a/patches/x509-store-1.6.5.patch +++ /dev/null @@ -1,31 +0,0 @@ -diff -ru x509-store-1.6.5.orig/Data/X509/CertificateStore.hs x509-store-1.6.5/Data/X509/CertificateStore.hs ---- x509-store-1.6.5.orig/Data/X509/CertificateStore.hs 2017-06-26 18:12:09.000000000 +0200 -+++ x509-store-1.6.5/Data/X509/CertificateStore.hs 2017-09-15 12:18:24.618736311 +0200 -@@ -11,6 +11,7 @@ - import Data.Either (rights) - import Data.List (foldl', isPrefixOf) - import Data.Monoid -+import Data.Semigroup - import Data.PEM (pemParseBS, pemContent) - import Data.X509 - import qualified Data.Map as M -@@ -26,12 +27,14 @@ - data CertificateStore = CertificateStore (M.Map DistinguishedName SignedCertificate) - | CertificateStores [CertificateStore] - -+instance Semigroup CertificateStore where -+ (<>) (CertificateStores l) s2@(CertificateStore _) = CertificateStores (l ++ [s2]) -+ (<>) s1@(CertificateStore _) (CertificateStores l) = CertificateStores ([s1] ++ l) -+ (<>) (CertificateStores l1) (CertificateStores l2) = CertificateStores (l1 ++ l2) -+ - instance Monoid CertificateStore where - mempty = CertificateStore M.empty -- mappend s1@(CertificateStore _) s2@(CertificateStore _) = CertificateStores [s1,s2] -- mappend (CertificateStores l) s2@(CertificateStore _) = CertificateStores (l ++ [s2]) -- mappend s1@(CertificateStore _) (CertificateStores l) = CertificateStores ([s1] ++ l) -- mappend (CertificateStores l1) (CertificateStores l2) = CertificateStores (l1 ++ l2) -+ mappend = (<>) - - -- | Create a certificate store out of a list of X509 certificate - makeCertificateStore :: [SignedCertificate] -> CertificateStore -Only in x509-store-1.6.5/Data/X509: CertificateStore.hs~ diff --git a/patches/xmonad-0.14.patch b/patches/xmonad-0.14.patch deleted file mode 100644 index 0ff201b21035f077f59d411de4d7fb8cfc53e59d..0000000000000000000000000000000000000000 --- a/patches/xmonad-0.14.patch +++ /dev/null @@ -1,16 +0,0 @@ -diff -ru xmonad-0.14.orig/src/XMonad/Core.hs xmonad-0.14/src/XMonad/Core.hs ---- xmonad-0.14.orig/src/XMonad/Core.hs 2018-07-30 05:12:59.000000000 -0400 -+++ xmonad-0.14/src/XMonad/Core.hs 2018-07-30 08:25:03.875705082 -0400 -@@ -434,7 +434,11 @@ - x - where - nullStdin = do -- fd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags -+ fd <- openFd "/dev/null" ReadOnly -+#if !(MIN_VERSION_unix(2,8,0)) -+ Nothing -+#endif -+ defaultFileFlags - dupTo fd stdInput - closeFd fd - diff --git a/patches/yaml-0.8.23.3.patch b/patches/yaml-0.8.23.3.patch deleted file mode 100644 index f2a1c34471c8d14aaeb82073e6ffd0f3249e1553..0000000000000000000000000000000000000000 --- a/patches/yaml-0.8.23.3.patch +++ /dev/null @@ -1,28 +0,0 @@ -diff -ru yaml-0.8.23.3.orig/Data/Yaml/Parser.hs yaml-0.8.23.3/Data/Yaml/Parser.hs ---- yaml-0.8.23.3.orig/Data/Yaml/Parser.hs 2017-06-16 05:46:12.000000000 +0200 -+++ yaml-0.8.23.3/Data/Yaml/Parser.hs 2017-09-17 10:51:54.961189093 +0200 -@@ -15,7 +15,9 @@ - import Data.Conduit - import Data.Conduit.Lift (runWriterC) - import qualified Data.Map as Map --#if !MIN_VERSION_base(4,8,0) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup -+#elif !MIN_VERSION_base(4,8,0) - import Data.Monoid (Monoid (..)) - #endif - import Data.Text (Text, pack, unpack) -@@ -36,9 +38,13 @@ - instance Alternative YamlParser where - empty = fail "empty" - (<|>) = mplus -+instance Semigroup (YamlParser a) where -+ (<>) = mplus - instance Monoid (YamlParser a) where - mempty = fail "mempty" -+#if !(MIN_VERSION_base(4,11,0)) - mappend = mplus -+#endif - instance Monad YamlParser where - return = pure - YamlParser f >>= g = YamlParser $ \am -> diff --git a/patches/yaml-0.8.25.1.patch b/patches/yaml-0.8.25.1.patch deleted file mode 100644 index 7427c45b4b0b7f4824862d48b438a804a1948ec8..0000000000000000000000000000000000000000 --- a/patches/yaml-0.8.25.1.patch +++ /dev/null @@ -1,23 +0,0 @@ -diff --git a/Data/Yaml/Parser.hs b/Data/Yaml/Parser.hs -index 2b9ee23..2791f2a 100644 ---- a/Data/Yaml/Parser.hs -+++ b/Data/Yaml/Parser.hs -@@ -22,6 +22,9 @@ import Data.Text (Text, pack, unpack) - import Data.Text.Encoding (decodeUtf8) - import Data.Text.Read (signed, decimal) - import Data.Typeable (Typeable) -+#if MIN_VERSION_base(4,9,0) -+import Data.Semigroup (Semigroup (..)) -+#endif - - import Text.Libyaml - -@@ -36,6 +39,8 @@ instance Applicative YamlParser where - instance Alternative YamlParser where - empty = fail "empty" - (<|>) = mplus -+instance Semigroup (YamlParser a) where -+ (<>) = mplus - instance Monoid (YamlParser a) where - mempty = fail "mempty" - mappend = mplus diff --git a/patches/yesod-core-1.6.0.patch b/patches/yesod-core-1.6.0.patch deleted file mode 100644 index 6f9a76cbd2967ecad08103ebc39d01e249f70110..0000000000000000000000000000000000000000 --- a/patches/yesod-core-1.6.0.patch +++ /dev/null @@ -1,157 +0,0 @@ -commit 3408e1e630f593ca93b5e79e7e7121a1fa813307 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sun Feb 4 19:49:16 2018 -0500 - - Adapt to Semigroup changes in base-4.11 - -diff --git a/ChangeLog.md b/ChangeLog.md -index b66fa67..8234e97 100644 ---- a/ChangeLog.md -+++ b/ChangeLog.md -@@ -1,3 +1,9 @@ -+## 1.6.1 -+ -+* Add a `Semigroup LiteApp` instance, and explicitly define `(<>)` in the -+ already existing `Semigroup` instances for `WidgetFor`, `Head`, `Body`, -+ `GWData`, and `UniqueList`. -+ - ## 1.6.0 - - * Upgrade to conduit 1.3.0 -diff --git a/Yesod/Core/Internal/LiteApp.hs b/Yesod/Core/Internal/LiteApp.hs -index c9a6f51..cc1a16d 100644 ---- a/Yesod/Core/Internal/LiteApp.hs -+++ b/Yesod/Core/Internal/LiteApp.hs -@@ -4,6 +4,9 @@ module Yesod.Core.Internal.LiteApp where - #if __GLASGOW_HASKELL__ < 710 - import Data.Monoid - #endif -+#if !(MIN_VERSION_base(4,11,0)) -+import Data.Semigroup (Semigroup(..)) -+#endif - import Yesod.Routes.Class - import Yesod.Core.Class.Yesod - import Yesod.Core.Class.Dispatch -@@ -42,9 +45,14 @@ instance RenderRoute LiteApp where - instance ParseRoute LiteApp where - parseRoute (x, _) = Just $ LiteAppRoute x - -+instance Semigroup LiteApp where -+ LiteApp x <> LiteApp y = LiteApp $ \m ps -> x m ps <|> y m ps -+ - instance Monoid LiteApp where - mempty = LiteApp $ \_ _ -> Nothing -- mappend (LiteApp x) (LiteApp y) = LiteApp $ \m ps -> x m ps <|> y m ps -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif - - type LiteHandler = HandlerFor LiteApp - type LiteWidget = WidgetFor LiteApp -diff --git a/Yesod/Core/Types.hs b/Yesod/Core/Types.hs -index 2bdf407..e55bc6a 100644 ---- a/Yesod/Core/Types.hs -+++ b/Yesod/Core/Types.hs -@@ -31,6 +31,7 @@ import Data.IORef (IORef, modifyIORef') - import Data.Map (Map, unionWith) - import qualified Data.Map as Map - import Data.Monoid (Endo (..), Last (..)) -+import Data.Semigroup (Semigroup(..)) - import Data.Serialize (Serialize (..), - putByteString) - import Data.String (IsString (fromString)) -@@ -55,12 +56,10 @@ import Web.Cookie (SetCookie) - import Yesod.Core.Internal.Util (getTime, putTime) - import Yesod.Routes.Class (RenderRoute (..), ParseRoute (..)) - import Control.Monad.Reader (MonadReader (..)) --import Data.Monoid ((<>)) - import Control.DeepSeq (NFData (rnf)) - import Control.DeepSeq.Generics (genericRnf) - import Yesod.Core.TypeCache (TypeMap, KeyedTypeMap) - import Control.Monad.Logger (MonadLoggerIO (..)) --import Data.Semigroup (Semigroup) - import UnliftIO (MonadUnliftIO (..), UnliftIO (..)) - - -- Sessions -@@ -255,8 +254,11 @@ data WidgetData site = WidgetData - - instance a ~ () => Monoid (WidgetFor site a) where - mempty = return () -- mappend x y = x >> y --instance a ~ () => Semigroup (WidgetFor site a) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+instance a ~ () => Semigroup (WidgetFor site a) where -+ x <> y = x >> y - - -- | A 'String' can be trivially promoted to a widget. - -- -@@ -356,11 +358,9 @@ data Stylesheet url = Stylesheet { styleLocation :: !(Location url), styleAttrib - newtype Title = Title { unTitle :: Html } - - newtype Head url = Head (HtmlUrl url) -- deriving Monoid --instance Semigroup (Head a) -+ deriving (Semigroup, Monoid) - newtype Body url = Body (HtmlUrl url) -- deriving Monoid --instance Semigroup (Body a) -+ deriving (Semigroup, Monoid) - - type CssBuilderUrl a = (a -> [(Text, Text)] -> Text) -> TBuilder.Builder - -@@ -375,16 +375,19 @@ data GWData a = GWData - } - instance Monoid (GWData a) where - mempty = GWData mempty mempty mempty mempty mempty mempty mempty -- mappend (GWData a1 a2 a3 a4 a5 a6 a7) -- (GWData b1 b2 b3 b4 b5 b6 b7) = GWData -- (a1 `mappend` b1) -- (a2 `mappend` b2) -- (a3 `mappend` b3) -- (a4 `mappend` b4) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+instance Semigroup (GWData a) where -+ GWData a1 a2 a3 a4 a5 a6 a7 <> -+ GWData b1 b2 b3 b4 b5 b6 b7 = GWData -+ (a1 <> b1) -+ (a2 <> b2) -+ (a3 <> b3) -+ (a4 <> b4) - (unionWith mappend a5 b5) -- (a6 `mappend` b6) -- (a7 `mappend` b7) --instance Semigroup (GWData a) -+ (a6 <> b6) -+ (a7 <> b7) - - data HandlerContents = - HCContent !H.Status !TypedContent -@@ -473,8 +476,11 @@ instance MonadLoggerIO (HandlerFor site) where - - instance Monoid (UniqueList x) where - mempty = UniqueList id -- UniqueList x `mappend` UniqueList y = UniqueList $ x . y --instance Semigroup (UniqueList x) -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+instance Semigroup (UniqueList x) where -+ UniqueList x <> UniqueList y = UniqueList $ x . y - - instance IsString Content where - fromString = flip ContentBuilder Nothing . BB.stringUtf8 -diff --git a/yesod-core.cabal b/yesod-core.cabal -index abefefc..38e27c9 100644 ---- a/yesod-core.cabal -+++ b/yesod-core.cabal -@@ -1,5 +1,5 @@ - name: yesod-core --version: 1.6.0 -+version: 1.6.1 - license: MIT - license-file: LICENSE - author: Michael Snoyman <michael@snoyman.com> diff --git a/patches/yesod-form-1.6.0.patch b/patches/yesod-form-1.6.0.patch deleted file mode 100644 index a48bd5cb4384adf64c454b791e95b5a6ac6a7059..0000000000000000000000000000000000000000 --- a/patches/yesod-form-1.6.0.patch +++ /dev/null @@ -1,48 +0,0 @@ -commit 3408e1e630f593ca93b5e79e7e7121a1fa813307 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sun Feb 4 19:49:16 2018 -0500 - - Adapt to Semigroup changes in base-4.11 - -diff --git a/ChangeLog.md b/ChangeLog.md -index 9af79a5..79a704b 100644 ---- a/ChangeLog.md -+++ b/ChangeLog.md -@@ -1,3 +1,7 @@ -+## 1.6.1 -+ -+* Explicitly define `(<>)` in the `Semigroup` instance for `Enctype` -+ - ## 1.6.0 - - * Upgrade to yesod-core 1.6.0 -diff --git a/Yesod/Form/Types.hs b/Yesod/Form/Types.hs -index bd4e91d..898e319 100644 ---- a/Yesod/Form/Types.hs -+++ b/Yesod/Form/Types.hs -@@ -104,9 +104,12 @@ instance ToValue Enctype where - toValue Multipart = "multipart/form-data" - instance Monoid Enctype where - mempty = UrlEncoded -- mappend UrlEncoded UrlEncoded = UrlEncoded -- mappend _ _ = Multipart --instance Semigroup Enctype -+#if !(MIN_VERSION_base(4,11,0)) -+ mappend = (<>) -+#endif -+instance Semigroup Enctype where -+ UrlEncoded <> UrlEncoded = UrlEncoded -+ _ <> _ = Multipart - - data Ints = IntCons Int Ints | IntSingle Int - instance Show Ints where -diff --git a/yesod-form.cabal b/yesod-form.cabal -index aa54488..adfcd2a 100644 ---- a/yesod-form.cabal -+++ b/yesod-form.cabal -@@ -1,5 +1,5 @@ - name: yesod-form --version: 1.6.0 -+version: 1.6.1 - license: MIT - license-file: LICENSE diff --git a/patches/yesod-test-1.6.0.patch b/patches/yesod-test-1.6.0.patch deleted file mode 100644 index 2a8fb750508dd2182b1c2bb8d2b6843eb07e2dae..0000000000000000000000000000000000000000 --- a/patches/yesod-test-1.6.0.patch +++ /dev/null @@ -1,59 +0,0 @@ -commit 3408e1e630f593ca93b5e79e7e7121a1fa813307 -Author: Ryan Scott <ryan.gl.scott@gmail.com> -Date: Sun Feb 4 19:49:16 2018 -0500 - - Adapt to Semigroup changes in base-4.11 - -diff --git a/ChangeLog.md b/ChangeLog.md -index 07c308e..55daaf2 100644 ---- a/ChangeLog.md -+++ b/ChangeLog.md -@@ -1,3 +1,7 @@ -+## 1.6.1 -+ -+* Fix the build with `base-4.11` (GHC 8.4). -+ - ## 1.6.0 - - * Upgrade to yesod-core 1.6.0 -diff --git a/Yesod/Test.hs b/Yesod/Test.hs -index 977e838..b3d4932 100644 ---- a/Yesod/Test.hs -+++ b/Yesod/Test.hs -@@ -158,6 +158,7 @@ import Data.Time.Clock (getCurrentTime) - import Control.Applicative ((<$>)) - import Text.Show.Pretty (ppShow) - import Data.Monoid (mempty) -+import Data.Semigroup (Semigroup(..)) - #if MIN_VERSION_base(4,9,0) - import GHC.Stack (HasCallStack) - #elif MIN_VERSION_base(4,8,1) -@@ -570,9 +571,6 @@ genericNameFromLabel match label = do - name:_ -> return name - _ -> failure $ "More than one label contained " <> label - --(<>) :: T.Text -> T.Text -> T.Text --(<>) = T.append -- - byLabelWithMatch :: (T.Text -> T.Text -> Bool) -- ^ The matching method which is used to find labels (i.e. exact, contains) - -> T.Text -- ^ The text contained in the @\<label>@. - -> T.Text -- ^ The value to set the parameter to. -diff --git a/yesod-test.cabal b/yesod-test.cabal -index 4e4a61d..6ed8c21 100644 ---- a/yesod-test.cabal -+++ b/yesod-test.cabal -@@ -1,5 +1,5 @@ - name: yesod-test --version: 1.6.0 -+version: 1.6.1 - license: MIT - license-file: LICENSE - author: Nubis <nubis@woobiz.com.ar> -@@ -30,6 +30,7 @@ library - , network >= 2.2 - , persistent >= 1.0 - , pretty-show >= 1.6 -+ , semigroups - , text - , time - , transformers >= 0.2.2