Script 'mail_helper' called by obssrc Hello community, here is the log from the commit of package ghc-bifunctors for openSUSE:Factory checked in at 2021-05-05 20:40:28 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-bifunctors (Old) and /work/SRC/openSUSE:Factory/.ghc-bifunctors.new.2988 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-bifunctors" Wed May 5 20:40:28 2021 rev:25 rq:890695 version:5.5.11 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-bifunctors/ghc-bifunctors.changes 2021-02-16 22:45:17.494330326 +0100 +++ /work/SRC/openSUSE:Factory/.ghc-bifunctors.new.2988/ghc-bifunctors.changes 2021-05-05 20:40:52.686686581 +0200 @@ -1,0 +2,8 @@ +Fri Apr 30 20:29:08 UTC 2021 - psim...@suse.com + +- Update bifunctors to version 5.5.11. + 5.5.11 [2021.04.30] + ------------------- + * Allow building with `template-haskell-2.18` (GHC 9.2). + +------------------------------------------------------------------- Old: ---- bifunctors-5.5.10.tar.gz New: ---- bifunctors-5.5.11.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-bifunctors.spec ++++++ --- /var/tmp/diff_new_pack.esp2K9/_old 2021-05-05 20:40:53.178684415 +0200 +++ /var/tmp/diff_new_pack.esp2K9/_new 2021-05-05 20:40:53.178684415 +0200 @@ -19,7 +19,7 @@ %global pkg_name bifunctors %bcond_with tests Name: ghc-%{pkg_name} -Version: 5.5.10 +Version: 5.5.11 Release: 0 Summary: Collection Haskell 98 bifunctors, bifoldables and bitraversables License: BSD-2-Clause ++++++ bifunctors-5.5.10.tar.gz -> bifunctors-5.5.11.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/bifunctors-5.5.10/CHANGELOG.markdown new/bifunctors-5.5.11/CHANGELOG.markdown --- old/bifunctors-5.5.10/CHANGELOG.markdown 2001-09-09 03:46:40.000000000 +0200 +++ new/bifunctors-5.5.11/CHANGELOG.markdown 2001-09-09 03:46:40.000000000 +0200 @@ -1,3 +1,7 @@ +5.5.11 [2021.04.30] +------------------- +* Allow building with `template-haskell-2.18` (GHC 9.2). + 5.5.10 [2021.01.21] ------------------- * Fix a bug in which `deriveBifoldable` could generate code that triggers diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/bifunctors-5.5.10/bifunctors.cabal new/bifunctors-5.5.11/bifunctors.cabal --- old/bifunctors-5.5.10/bifunctors.cabal 2001-09-09 03:46:40.000000000 +0200 +++ new/bifunctors-5.5.11/bifunctors.cabal 2001-09-09 03:46:40.000000000 +0200 @@ -1,6 +1,6 @@ name: bifunctors category: Data, Functors -version: 5.5.10 +version: 5.5.11 license: BSD3 cabal-version: >= 1.10 license-file: LICENSE @@ -23,8 +23,9 @@ , GHC == 8.2.2 , GHC == 8.4.4 , GHC == 8.6.5 - , GHC == 8.8.3 - , GHC == 8.10.1 + , GHC == 8.8.4 + , GHC == 8.10.4 + , GHC == 9.0.1 extra-source-files: CHANGELOG.markdown README.markdown @@ -59,7 +60,7 @@ base-orphans >= 0.8.4 && < 1, comonad >= 5.0.7 && < 6, containers >= 0.2 && < 0.7, - template-haskell >= 2.4 && < 2.18, + template-haskell >= 2.4 && < 2.19, th-abstraction >= 0.4.2.0 && < 0.5, transformers >= 0.3 && < 0.6 diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/bifunctors-5.5.10/src/Data/Bifunctor/TH/Internal.hs new/bifunctors-5.5.11/src/Data/Bifunctor/TH/Internal.hs --- old/bifunctors-5.5.10/src/Data/Bifunctor/TH/Internal.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/bifunctors-5.5.11/src/Data/Bifunctor/TH/Internal.hs 2001-09-09 03:46:40.000000000 +0200 @@ -16,7 +16,7 @@ module Data.Bifunctor.TH.Internal where import Data.Foldable (foldr') -import Data.List +import qualified Data.List as List import qualified Data.Map as Map (singleton) import Data.Map (Map) import Data.Maybe (fromMaybe, mapMaybe) @@ -334,7 +334,7 @@ -- | Construct a type via curried application. applyTy :: Type -> [Type] -> Type -applyTy = foldl' AppT +applyTy = List.foldl' AppT -- | Fully applies a type constructor to its type variables. applyTyCon :: Name -> [Type] -> Type diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/bifunctors-5.5.10/src/Data/Bifunctor/TH.hs new/bifunctors-5.5.11/src/Data/Bifunctor/TH.hs --- old/bifunctors-5.5.10/src/Data/Bifunctor/TH.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/bifunctors-5.5.11/src/Data/Bifunctor/TH.hs 2001-09-09 03:46:40.000000000 +0200 @@ -65,7 +65,7 @@ import Control.Monad (guard, unless, when) import Data.Bifunctor.TH.Internal -import Data.List +import qualified Data.List as List import qualified Data.Map as Map ((!), fromList, keys, lookup, member, size) import Data.Maybe @@ -629,7 +629,7 @@ mkApCon :: Exp -> [Exp] -> Exp mkApCon conExp [] = VarE pureValName `AppE` conExp mkApCon conExp [e] = VarE fmapValName `AppE` conExp `AppE` e - mkApCon conExp (e1:e2:es) = foldl' appAp + mkApCon conExp (e1:e2:es) = List.foldl' appAp (VarE liftA2ValName `AppE` conExp `AppE` e1 `AppE` e2) es where appAp se1 se2 = InfixE (Just se1) (VarE apValName) (Just se2) @@ -725,7 +725,7 @@ -- instance C (Fam [Char]) remainingTysOrigSubst :: [Type] remainingTysOrigSubst = - map (substNamesWithKindStar (union droppedKindVarNames kvNames')) + map (substNamesWithKindStar (List.union droppedKindVarNames kvNames')) $ take remainingLength instTysOrig isDataFamily :: Bool @@ -1252,7 +1252,7 @@ -> Q Match mkSimpleConMatch fold conName insides = do varsNeeded <- newNameList "_arg" $ length insides - let pat = ConP conName (map VarP varsNeeded) + let pat = conPCompat conName (map VarP varsNeeded) rhs <- fold conName (zipWith (\i v -> i $ VarE v) insides varsNeeded) return $ Match pat (NormalB rhs) [] @@ -1276,7 +1276,7 @@ -> Q Match mkSimpleConMatch2 fold conName insides = do varsNeeded <- newNameList "_arg" lengthInsides - let pat = ConP conName (map VarP varsNeeded) + let pat = conPCompat conName (map VarP varsNeeded) -- Make sure to zip BEFORE invoking catMaybes. We want the variable -- indicies in each expression to match up with the argument indices -- in conExpr (defined below). @@ -1324,3 +1324,11 @@ #endif m <- matchForCon tupDataName insides return $ CaseE x [m] + +-- Adapt to the type of ConP changing in template-haskell-2.18.0.0. +conPCompat :: Name -> [Pat] -> Pat +conPCompat n pats = ConP n +#if MIN_VERSION_template_haskell(2,18,0) + [] +#endif + pats diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/bifunctors-5.5.10/tests/BifunctorSpec.hs new/bifunctors-5.5.11/tests/BifunctorSpec.hs --- old/bifunctors-5.5.10/tests/BifunctorSpec.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/bifunctors-5.5.11/tests/BifunctorSpec.hs 2001-09-09 03:46:40.000000000 +0200 @@ -37,7 +37,7 @@ import Data.Bitraversable import Data.Char (chr) -import Data.Functor.Classes (Eq1) +import Data.Functor.Classes (Eq1, Show1) import Data.Functor.Compose (Compose(..)) import Data.Functor.Identity (Identity(..)) import Data.Monoid @@ -336,42 +336,45 @@ ------------------------------------------------------------------------------- -prop_BifunctorLaws :: (Bifunctor p, Eq (p a b), Eq (p c d)) - => (a -> c) -> (b -> d) -> p a b -> Bool -prop_BifunctorLaws f g x = - bimap id id x == x - && first id x == x - && second id x == x - && bimap f g x == (first f . second g) x +prop_BifunctorLaws :: (Bifunctor p, Eq (p a b), Eq (p c d), Show (p a b), Show (p c d)) + => (a -> c) -> (b -> d) -> p a b -> Expectation +prop_BifunctorLaws f g x = do + bimap id id x `shouldBe` x + first id x `shouldBe` x + second id x `shouldBe` x + bimap f g x `shouldBe` (first f . second g) x -prop_BifunctorEx :: (Bifunctor p, Eq (p [Int] [Int])) => p [Int] [Int] -> Bool +prop_BifunctorEx :: (Bifunctor p, Eq (p [Int] [Int]), Show (p [Int] [Int])) => p [Int] [Int] -> Expectation prop_BifunctorEx = prop_BifunctorLaws reverse (++ [42]) -prop_BifoldableLaws :: (Eq a, Eq b, Eq z, Monoid a, Monoid b, Bifoldable p) +prop_BifoldableLaws :: (Eq a, Eq b, Eq z, Show a, Show b, Show z, + Monoid a, Monoid b, Bifoldable p) => (a -> b) -> (a -> b) -> (a -> z -> z) -> (a -> z -> z) - -> z -> p a a -> Bool -prop_BifoldableLaws f g h i z x = - bifold x == bifoldMap id id x - && bifoldMap f g x == bifoldr (mappend . f) (mappend . g) mempty x - && bifoldr h i z x == appEndo (bifoldMap (Endo . h) (Endo . i) x) z + -> z -> p a a -> Expectation +prop_BifoldableLaws f g h i z x = do + bifold x `shouldBe` bifoldMap id id x + bifoldMap f g x `shouldBe` bifoldr (mappend . f) (mappend . g) mempty x + bifoldr h i z x `shouldBe` appEndo (bifoldMap (Endo . h) (Endo . i) x) z -prop_BifoldableEx :: Bifoldable p => p [Int] [Int] -> Bool +prop_BifoldableEx :: Bifoldable p => p [Int] [Int] -> Expectation prop_BifoldableEx = prop_BifoldableLaws reverse (++ [42]) ((+) . length) ((*) . length) 0 prop_BitraversableLaws :: (Applicative f, Applicative g, Bitraversable p, - Eq (g (p c c)), Eq (p a b), Eq (p d e), Eq1 f) + Eq (g (p c c)), Eq (p a b), Eq (p d e), Eq1 f, + Show (g (p c c)), Show (p a b), Show (p d e), Show1 f) => (a -> f c) -> (b -> f c) -> (c -> f d) -> (c -> f e) - -> (forall x. f x -> g x) -> p a b -> Bool -prop_BitraversableLaws f g h i t x = - bitraverse (t . f) (t . g) x == (t . bitraverse f g) x - && bitraverse Identity Identity x == Identity x - && (Compose . fmap (bitraverse h i) . bitraverse f g) x - == bitraverse (Compose . fmap h . f) (Compose . fmap i . g) x - -prop_BitraversableEx :: (Bitraversable p, Eq (p Char Char), - Eq (p [Char] [Char]), Eq (p [Int] [Int])) - => p [Int] [Int] -> Bool + -> (forall x. f x -> g x) -> p a b -> Expectation +prop_BitraversableLaws f g h i t x = do + bitraverse (t . f) (t . g) x `shouldBe` (t . bitraverse f g) x + bitraverse Identity Identity x `shouldBe` Identity x + (Compose . fmap (bitraverse h i) . bitraverse f g) x + `shouldBe` bitraverse (Compose . fmap h . f) (Compose . fmap i . g) x + +prop_BitraversableEx :: (Bitraversable p, + Eq (p Char Char), Eq (p [Char] [Char]), Eq (p [Int] [Int]), + Show (p Char Char), Show (p [Char] [Char]), Show (p [Int] [Int])) + => p [Int] [Int] -> Expectation prop_BitraversableEx = prop_BitraversableLaws (replicate 2 . map (chr . abs)) (replicate 4 . map (chr . abs)) @@ -388,17 +391,17 @@ spec = do describe "OneTwoCompose Maybe Either [Int] [Int]" $ do prop "satisfies the Bifunctor laws" - (prop_BifunctorEx :: OneTwoCompose Maybe Either [Int] [Int] -> Bool) + (prop_BifunctorEx :: OneTwoCompose Maybe Either [Int] [Int] -> Expectation) prop "satisfies the Bifoldable laws" - (prop_BifoldableEx :: OneTwoCompose Maybe Either [Int] [Int] -> Bool) + (prop_BifoldableEx :: OneTwoCompose Maybe Either [Int] [Int] -> Expectation) prop "satisfies the Bitraversable laws" - (prop_BitraversableEx :: OneTwoCompose Maybe Either [Int] [Int] -> Bool) + (prop_BitraversableEx :: OneTwoCompose Maybe Either [Int] [Int] -> Expectation) #if MIN_VERSION_template_haskell(2,7,0) describe "OneTwoComposeFam Maybe Either [Int] [Int]" $ do prop "satisfies the Bifunctor laws" - (prop_BifunctorEx :: OneTwoComposeFam Maybe Either [Int] [Int] -> Bool) + (prop_BifunctorEx :: OneTwoComposeFam Maybe Either [Int] [Int] -> Expectation) prop "satisfies the Bifoldable laws" - (prop_BifoldableEx :: OneTwoComposeFam Maybe Either [Int] [Int] -> Bool) + (prop_BifoldableEx :: OneTwoComposeFam Maybe Either [Int] [Int] -> Expectation) prop "satisfies the Bitraversable laws" - (prop_BitraversableEx :: OneTwoComposeFam Maybe Either [Int] [Int] -> Bool) + (prop_BitraversableEx :: OneTwoComposeFam Maybe Either [Int] [Int] -> Expectation) #endif