Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-bloomfilter for openSUSE:Factory 
checked in at 2023-08-18 19:27:58
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-bloomfilter (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-bloomfilter.new.1766 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-bloomfilter"

Fri Aug 18 19:27:58 2023 rev:7 rq:1104403 version:2.0.1.2

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-bloomfilter/ghc-bloomfilter.changes  
2023-04-04 21:25:43.719001051 +0200
+++ 
/work/SRC/openSUSE:Factory/.ghc-bloomfilter.new.1766/ghc-bloomfilter.changes    
    2023-08-18 19:28:10.339295799 +0200
@@ -1,0 +2,11 @@
+Fri Aug  4 19:23:09 UTC 2023 - Peter Simons <[email protected]>
+
+- Update bloomfilter to version 2.0.1.2.
+  * Fix Data.BloomFilter.Easy on 32 bit to not incorrectly fail with
+    "capacity too large to represent".
+  * Fix build with GHC 9.2, thanks to Simon Jakobi.
+
+- Drop "0001-Adapt-FastShift-instances-for-Word32-to-ghc-9.4.x.patch"
+  which is no longer necessary.
+
+-------------------------------------------------------------------

Old:
----
  0001-Adapt-FastShift-instances-for-Word32-to-ghc-9.4.x.patch
  bloomfilter-2.0.1.0.tar.gz
  bloomfilter.cabal

New:
----
  bloomfilter-2.0.1.2.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-bloomfilter.spec ++++++
--- /var/tmp/diff_new_pack.mLL1Ok/_old  2023-08-18 19:28:11.175297298 +0200
+++ /var/tmp/diff_new_pack.mLL1Ok/_new  2023-08-18 19:28:11.179297305 +0200
@@ -20,14 +20,12 @@
 %global pkgver %{pkg_name}-%{version}
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        2.0.1.0
+Version:        2.0.1.2
 Release:        0
 Summary:        Pure and impure Bloom Filter implementations
 License:        BSD-3-Clause
 URL:            https://hackage.haskell.org/package/%{pkg_name}
 Source0:        
https://hackage.haskell.org/package/%{pkg_name}-%{version}/%{pkg_name}-%{version}.tar.gz
-Source1:        
https://hackage.haskell.org/package/%{pkg_name}-%{version}/revision/2.cabal#/%{pkg_name}.cabal
-Patch1:         0001-Adapt-FastShift-instances-for-Word32-to-ghc-9.4.x.patch
 BuildRequires:  ghc-Cabal-devel
 BuildRequires:  ghc-array-devel
 BuildRequires:  ghc-array-prof
@@ -80,9 +78,7 @@
 This package provides the Haskell %{pkg_name} profiling library.
 
 %prep
-%autosetup -p1 -n %{pkg_name}-%{version}
-cp -p %{SOURCE1} %{pkg_name}.cabal
-cabal-tweak-dep-ver base '>= 4.4 && < 4.16' '< 5'
+%autosetup -n %{pkg_name}-%{version}
 
 %build
 %ghc_lib_build
@@ -103,7 +99,7 @@
 %license LICENSE
 
 %files devel -f %{name}-devel.files
-%doc README.markdown examples
+%doc CHANGELOG.md README.markdown examples
 
 %files -n ghc-%{pkg_name}-doc -f ghc-%{pkg_name}-doc.files
 %license LICENSE

++++++ bloomfilter-2.0.1.0.tar.gz -> bloomfilter-2.0.1.2.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/CHANGELOG.md 
new/bloomfilter-2.0.1.2/CHANGELOG.md
--- old/bloomfilter-2.0.1.0/CHANGELOG.md        1970-01-01 01:00:00.000000000 
+0100
+++ new/bloomfilter-2.0.1.2/CHANGELOG.md        2001-09-09 03:46:40.000000000 
+0200
@@ -0,0 +1,9 @@
+#### 2.0.1.2
+* Fix Data.BloomFilter.Easy on 32 bit to not incorrectly fail with
+  "capacity too large to represent".
+
+#### 2.0.1.1
+* Fix build with GHC 9.2, thanks to Simon Jakobi.
+* Add CI with GitHub Actions, thanks to Simon Jakobi.
+* New maintainer for the package, 
+  under the https://github.com/haskell-pkg-janitors umbrella.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/Data/BloomFilter/Easy.hs 
new/bloomfilter-2.0.1.2/Data/BloomFilter/Easy.hs
--- old/bloomfilter-2.0.1.0/Data/BloomFilter/Easy.hs    2015-05-19 
05:14:07.000000000 +0200
+++ new/bloomfilter-2.0.1.2/Data/BloomFilter/Easy.hs    2001-09-09 
03:46:40.000000000 +0200
@@ -72,9 +72,14 @@
             minimum [((-k) * cap / log (1 - (errRate ** (1 / k))), k)
                      | k <- [1..100]]
         roundedBits = nextPowerOfTwo (ceiling bits)
-    in if roundedBits <= 0 || roundedBits > 0xffffffff
+    in if roundedBits <= 0 || maxbitstoolarge roundedBits
        then Left  "capacity too large to represent"
        else Right (roundedBits, truncate hashes)
+  where
+    maxbits = 0xffffffff
+    -- On 32 bit, maxbits is larger than maxBound :: Int, so wraps around
+    -- to a negative number; avoid using it in that case.
+    maxbitstoolarge n = if maxbits > 0 then n > maxbits else True
 
 -- | Behaves as 'safeSuggestSizing', but calls 'error' if given
 -- invalid or out-of-range inputs.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/Data/BloomFilter/Hash.hs 
new/bloomfilter-2.0.1.2/Data/BloomFilter/Hash.hs
--- old/bloomfilter-2.0.1.0/Data/BloomFilter/Hash.hs    2015-05-19 
05:14:07.000000000 +0200
+++ new/bloomfilter-2.0.1.2/Data/BloomFilter/Hash.hs    2001-09-09 
03:46:40.000000000 +0200
@@ -38,8 +38,7 @@
     ) where
 
 import Control.Monad (foldM)
-import Data.Bits ((.&.), (.|.), xor)
-import Data.BloomFilter.Util (FastShift(..))
+import Data.Bits ((.&.), (.|.), unsafeShiftL, unsafeShiftR, xor)
 import Data.List (unfoldr)
 import Data.Int (Int8, Int16, Int32, Int64)
 import Data.Word (Word8, Word16, Word32, Word64)
@@ -91,11 +90,11 @@
              -> Word64           -- ^ salt
              -> IO Word64
     hashIO64 v salt = do
-                   let s1 = fromIntegral (salt `shiftR` 32) .&. maxBound
+                   let s1 = fromIntegral (salt `unsafeShiftR` 32) .&. maxBound
                        s2 = fromIntegral salt
                    h1 <- hashIO32 v s1
                    h2 <- hashIO32 v s2
-                   return $ (fromIntegral h1 `shiftL` 32) .|. fromIntegral h2
+                   return $ (fromIntegral h1 `unsafeShiftL` 32) .|. 
fromIntegral h2
 
 -- | Compute a 32-bit hash.
 hash32 :: Hashable a => a -> Word32
@@ -149,8 +148,8 @@
 cheapHashes k v = go 0
     where go i | i == j = []
                | otherwise = hash : go (i + 1)
-               where !hash = h1 + (h2 `shiftR` i)
-          h1 = fromIntegral (h `shiftR` 32)
+               where !hash = h1 + (h2 `unsafeShiftR` i)
+          h1 = fromIntegral (h `unsafeShiftR` 32)
           h2 = fromIntegral h
           h = hashSalt64 0x9150a946c4a8966e v
           j = fromIntegral k
@@ -163,7 +162,7 @@
                                    (salt `xor` 0x3ece731e)
                   | otherwise = hashIO32 (unfoldr go k) salt
         where go 0 = Nothing
-              go i = Just (fromIntegral i :: Word32, i `shiftR` 32)
+              go i = Just (fromIntegral i :: Word32, i `unsafeShiftR` 32)
 
 instance Hashable Bool where
     hashIO32 = hashOne32
@@ -224,7 +223,7 @@
 -- | A fast unchecked shift.  Nasty, but otherwise GHC 6.8.2 does a
 -- test and branch on every shift.
 div4 :: CSize -> CSize
-div4 k = fromIntegral ((fromIntegral k :: HTYPE_SIZE_T) `shiftR` 2)
+div4 k = fromIntegral ((fromIntegral k :: HTYPE_SIZE_T) `unsafeShiftR` 2)
 
 alignedHash :: Ptr a -> CSize -> Word32 -> IO Word32
 alignedHash ptr bytes salt
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/Data/BloomFilter/Mutable.hs 
new/bloomfilter-2.0.1.2/Data/BloomFilter/Mutable.hs
--- old/bloomfilter-2.0.1.0/Data/BloomFilter/Mutable.hs 2015-05-19 
05:14:07.000000000 +0200
+++ new/bloomfilter-2.0.1.2/Data/BloomFilter/Mutable.hs 2001-09-09 
03:46:40.000000000 +0200
@@ -65,9 +65,9 @@
 import Control.Monad (liftM, forM_)
 import Control.Monad.ST (ST)
 import Data.Array.Base (unsafeRead, unsafeWrite)
-import Data.Bits ((.&.), (.|.))
+import Data.Bits ((.&.), (.|.), unsafeShiftL, unsafeShiftR)
 import Data.BloomFilter.Array (newArray)
-import Data.BloomFilter.Util (FastShift(..), (:*)(..), nextPowerOfTwo)
+import Data.BloomFilter.Util ((:*)(..), nextPowerOfTwo)
 import Data.Word (Word32)
 import Data.BloomFilter.Mutable.Internal
 
@@ -86,9 +86,9 @@
                 | numBits > maxHash = maxHash
                 | isPowerOfTwo numBits = numBits
                 | otherwise = nextPowerOfTwo numBits
-        numElems = max 2 (twoBits `shiftR` logBitsInHash)
-        numBytes = numElems `shiftL` logBytesInHash
-        trueBits = numElems `shiftL` logBitsInHash
+        numElems = max 2 (twoBits `unsafeShiftR` logBitsInHash)
+        numBytes = numElems `unsafeShiftL` logBytesInHash
+        trueBits = numElems `unsafeShiftL` logBitsInHash
         shft     = logPower2 trueBits
         msk      = trueBits - 1
         isPowerOfTwo n = n .&. (n - 1) == 0
@@ -109,7 +109,7 @@
 -- | Given a filter's mask and a hash value, compute an offset into
 -- a word array and a bit offset within that word.
 hashIdx :: Int -> Word32 -> (Int :* Int)
-hashIdx msk x = (y `shiftR` logBitsInHash) :* (y .&. hashMask)
+hashIdx msk x = (y `unsafeShiftR` logBitsInHash) :* (y .&. hashMask)
   where hashMask = 31 -- bitsInHash - 1
         y = fromIntegral x .&. msk
 
@@ -125,7 +125,7 @@
   let mu = bitArray mb
   forM_ (hashesM mb elt) $ \(word :* bit) -> do
       old <- unsafeRead mu word
-      unsafeWrite mu word (old .|. (1 `shiftL` bit))
+      unsafeWrite mu word (old .|. (1 `unsafeShiftL` bit))
 
 -- | Query a mutable Bloom filter for membership.  If the value is
 -- present, return @True@.  If the value is not present, there is
@@ -135,7 +135,7 @@
   where mu = bitArray mb
         loop ((word :* bit):wbs) = do
           i <- unsafeRead mu word
-          if i .&. (1 `shiftL` bit) == 0
+          if i .&. (1 `unsafeShiftL` bit) == 0
             then return False
             else loop wbs
         loop _ = return True
@@ -145,7 +145,7 @@
 
 -- | Return the size of a mutable Bloom filter, in bits.
 length :: MBloom s a -> Int
-length = shiftL 1 . shift
+length = unsafeShiftL 1 . shift
 
 
 -- | Slow, crummy way of computing the integer log of an integer known
@@ -153,7 +153,7 @@
 logPower2 :: Int -> Int
 logPower2 k = go 0 k
     where go j 1 = j
-          go j n = go (j+1) (n `shiftR` 1)
+          go j n = go (j+1) (n `unsafeShiftR` 1)
 
 -- $overview
 --
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/Data/BloomFilter/Util.hs 
new/bloomfilter-2.0.1.2/Data/BloomFilter/Util.hs
--- old/bloomfilter-2.0.1.0/Data/BloomFilter/Util.hs    2015-05-19 
05:14:07.000000000 +0200
+++ new/bloomfilter-2.0.1.2/Data/BloomFilter/Util.hs    2001-09-09 
03:46:40.000000000 +0200
@@ -2,15 +2,11 @@
 
 module Data.BloomFilter.Util
     (
-      FastShift(..)
-    , nextPowerOfTwo
+      nextPowerOfTwo
     , (:*)(..)
     ) where
 
-import Data.Bits ((.|.))
-import qualified Data.Bits as Bits
-import GHC.Base
-import GHC.Word
+import Data.Bits ((.|.), unsafeShiftR)
 
 -- | A strict pair type.
 data a :* b = !a :* !b
@@ -22,46 +18,11 @@
 {-# INLINE nextPowerOfTwo #-}
 nextPowerOfTwo n =
     let a = n - 1
-        b = a .|. (a `shiftR` 1)
-        c = b .|. (b `shiftR` 2)
-        d = c .|. (c `shiftR` 4)
-        e = d .|. (d `shiftR` 8)
-        f = e .|. (e `shiftR` 16)
-        g = f .|. (f `shiftR` 32)  -- in case we're on a 64-bit host
+        b = a .|. (a `unsafeShiftR` 1)
+        c = b .|. (b `unsafeShiftR` 2)
+        d = c .|. (c `unsafeShiftR` 4)
+        e = d .|. (d `unsafeShiftR` 8)
+        f = e .|. (e `unsafeShiftR` 16)
+        g = f .|. (f `unsafeShiftR` 32)  -- in case we're on a 64-bit host
         !h = g + 1
     in h
-
--- | This is a workaround for poor optimisation in GHC 6.8.2.  It
--- fails to notice constant-width shifts, and adds a test and branch
--- to every shift.  This imposes about a 10% performance hit.
-class FastShift a where
-    shiftL :: a -> Int -> a
-    shiftR :: a -> Int -> a
-
-instance FastShift Word32 where
-    {-# INLINE shiftL #-}
-    shiftL (W32# x#) (I# i#) = W32# (x# `uncheckedShiftL#` i#)
-
-    {-# INLINE shiftR #-}
-    shiftR (W32# x#) (I# i#) = W32# (x# `uncheckedShiftRL#` i#)
-
-instance FastShift Word64 where
-    {-# INLINE shiftL #-}
-    shiftL (W64# x#) (I# i#) = W64# (x# `uncheckedShiftL64#` i#)
-
-    {-# INLINE shiftR #-}
-    shiftR (W64# x#) (I# i#) = W64# (x# `uncheckedShiftRL64#` i#)
-
-instance FastShift Int where
-    {-# INLINE shiftL #-}
-    shiftL (I# x#) (I# i#) = I# (x# `iShiftL#` i#)
-
-    {-# INLINE shiftR #-}
-    shiftR (I# x#) (I# i#) = I# (x# `iShiftRA#` i#)
-
-instance FastShift Integer where
-    {-# INLINE shiftL #-}
-    shiftL = Bits.shiftL
-
-    {-# INLINE shiftR #-}
-    shiftR = Bits.shiftR
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/Data/BloomFilter.hs 
new/bloomfilter-2.0.1.2/Data/BloomFilter.hs
--- old/bloomfilter-2.0.1.0/Data/BloomFilter.hs 2015-05-19 05:14:07.000000000 
+0200
+++ new/bloomfilter-2.0.1.2/Data/BloomFilter.hs 2001-09-09 03:46:40.000000000 
+0200
@@ -78,8 +78,8 @@
 import Data.Array.Base (unsafeAt)
 import qualified Data.Array.Base as ST
 import Data.Array.Unboxed (UArray)
-import Data.Bits ((.&.))
-import Data.BloomFilter.Util (FastShift(..), (:*)(..))
+import Data.Bits ((.&.), unsafeShiftL, unsafeShiftR)
+import Data.BloomFilter.Util ((:*)(..))
 import qualified Data.BloomFilter.Mutable as MB
 import qualified Data.BloomFilter.Mutable.Internal as MB
 import Data.BloomFilter.Mutable.Internal (Hash, MBloom)
@@ -98,13 +98,13 @@
     }
 
 instance Show (Bloom a) where
-    show ub = "Bloom { " ++ show ((1::Int) `shiftL` shift ub) ++ " bits } "
+    show ub = "Bloom { " ++ show ((1::Int) `unsafeShiftL` shift ub) ++ " bits 
} "
 
 instance NFData (Bloom a) where
     rnf !_ = ()
 
 logBitsInHash :: Int
-logBitsInHash = 5 -- logPower2 bitsInHash
+logBitsInHash = 5 -- Data.BloomFilter.Mutable.logPower2 bitsInHash
 
 -- | Create an immutable Bloom filter, using the given setup function
 -- which executes in the 'ST' monad.
@@ -172,14 +172,9 @@
 -- | Given a filter's mask and a hash value, compute an offset into
 -- a word array and a bit offset within that word.
 hashIdx :: Int -> Word32 -> (Int :* Int)
-hashIdx mask x = (y `shiftR` logBitsInHash) :* (y .&. hashMask)
+hashIdx msk x = (y `unsafeShiftR` logBitsInHash) :* (y .&. hashMask)
   where hashMask = 31 -- bitsInHash - 1
-        y = fromIntegral x .&. mask
-
--- | Hash the given value, returning a list of (word offset, bit
--- offset) pairs, one per hash value.
-hashesM :: MBloom s a -> a -> [Int :* Int]
-hashesM mb elt = hashIdx (MB.mask mb) `map` MB.hashes mb elt
+        y = fromIntegral x .&. msk
 
 -- | Hash the given value, returning a list of (word offset, bit
 -- offset) pairs, one per hash value.
@@ -191,7 +186,7 @@
 -- /still/ some possibility that @True@ will be returned.
 elem :: a -> Bloom a -> Bool
 elem elt ub = all test (hashesU ub elt)
-  where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `shiftL` bit) 
/= 0
+  where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `unsafeShiftL` 
bit) /= 0
           
 modify :: (forall s. (MBloom s a -> ST s z))  -- ^ mutation function (result 
is discarded)
         -> Bloom a
@@ -252,14 +247,14 @@
 
 -- | Query an immutable Bloom filter for non-membership.  If the value
 -- /is/ present, return @False@.  If the value is not present, there
--- is /still/ some possibility that @True@ will be returned.
+-- is /still/ some possibility that @False@ will be returned.
 notElem :: a -> Bloom a -> Bool
 notElem elt ub = any test (hashesU ub elt)
-  where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `shiftL` bit) 
== 0
+  where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `unsafeShiftL` 
bit) == 0
 
 -- | Return the size of an immutable Bloom filter, in bits.
 length :: Bloom a -> Int
-length = shiftL 1 . shift
+length = unsafeShiftL 1 . shift
 
 -- | Build an immutable Bloom filter from a seed value.  The seeding
 -- function populates the filter as follows.
@@ -275,7 +270,7 @@
         -> b                         -- ^ initial seed
         -> Bloom a
 {-# INLINE unfold #-}
-unfold hashes numBits f k = create hashes numBits (loop k)
+unfold hs numBits f k = create hs numBits (loop k)
   where loop :: forall s. b -> MBloom s a -> ST s ()
         loop j mb = case f j of
                       Just (a, j') -> MB.insert mb a >> loop j' mb
@@ -298,7 +293,7 @@
           -> [a]                -- ^ values to populate with
           -> Bloom a
 {-# INLINE [1] fromList #-}
-fromList hashes numBits list = create hashes numBits $ forM_ list . MB.insert
+fromList hs numBits list = create hs numBits $ forM_ list . MB.insert
 
 {-# RULES "Bloom insertList . fromList" forall h n xs ys.
     insertList xs (fromList h n ys) = fromList h n (xs ++ ys)
@@ -313,13 +308,6 @@
         convert _      = Nothing
 -}
 
--- | Slow, crummy way of computing the integer log of an integer known
--- to be a power of two.
-logPower2 :: Int -> Int
-logPower2 k = go 0 k
-    where go j 1 = j
-          go j n = go (j+1) (n `shiftR` 1)
-
 -- $overview
 --
 -- Each of the functions for creating Bloom filters accepts two parameters:
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/README.markdown 
new/bloomfilter-2.0.1.2/README.markdown
--- old/bloomfilter-2.0.1.0/README.markdown     2015-05-19 05:14:07.000000000 
+0200
+++ new/bloomfilter-2.0.1.2/README.markdown     2001-09-09 03:46:40.000000000 
+0200
@@ -17,20 +17,13 @@
 # Get involved!
 
 Please report bugs via the
-[github issue tracker](https://github.com/bos/bloomfilter).
+[github issue tracker](https://github.com/haskell-pkg-janitors/bloomfilter).
 
-Master [git repository](https://github.com/bos/bloomfilter):
+Master [git repository](https://github.com/haskell-pkg-janitors/bloomfilter):
 
-* `git clone git://github.com/bos/bloomfilter.git`
-
-There's also a [Mercurial mirror](https://bitbucket.org/bos/bloomfilter):
-
-* `hg clone https://bitbucket.org/bos/bloomfilter`
-
-(You can create and contribute changes using either Mercurial or git.)
+* `git clone git://github.com/haskell-pkg-janitors/bloomfilter.git`
 
 
 # Authors
 
-This library is written and maintained by Bryan O'Sullivan,
-<[email protected]>.
+This library is written by Bryan O'Sullivan, <[email protected]>.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/bloomfilter-2.0.1.0/bloomfilter.cabal 
new/bloomfilter-2.0.1.2/bloomfilter.cabal
--- old/bloomfilter-2.0.1.0/bloomfilter.cabal   2015-05-19 05:14:07.000000000 
+0200
+++ new/bloomfilter-2.0.1.2/bloomfilter.cabal   2001-09-09 03:46:40.000000000 
+0200
@@ -1,24 +1,39 @@
+cabal-version:   3.0
 name:            bloomfilter
-version:         2.0.1.0
-license:         BSD3
+version:         2.0.1.2
+license:         BSD-3-Clause
 license-file:    LICENSE
 author:          Bryan O'Sullivan <[email protected]>
-maintainer:      Bryan O'Sullivan <[email protected]>
-homepage:        https://github.com/bos/bloomfilter
-bug-reports:     https://github.com/bos/bloomfilter/issues
+maintainer:      Joey Hess <[email protected]>
+homepage:        https://github.com/haskell-pkg-janitors/bloomfilter
+bug-reports:     https://github.com/haskell-pkg-janitors/bloomfilter/issues
 description:     Pure and impure Bloom Filter implementations.
 synopsis:        Pure and impure Bloom Filter implementations.
 category:        Data
 stability:       provisional
 build-type:      Simple
-cabal-version:   >= 1.8
-extra-source-files: README.markdown cbits/lookup3.c cbits/lookup3.h
+extra-source-files: README.markdown CHANGELOG.md
+                 cbits/lookup3.c cbits/lookup3.h
                  examples/Makefile examples/SpellChecker.hs examples/Words.hs
+tested-with:
+  GHC == 9.2.1
+  GHC == 9.0.1
+  GHC == 8.10.7
+  GHC == 8.8.4
+  GHC == 8.6.5
+  GHC == 8.4.4
+  GHC == 8.2.2
+  GHC == 8.0.2
+  GHC == 7.10.3
+  GHC == 7.8.4
+  GHC == 7.6.3
+  GHC == 7.4.2
 
 library
+  default-language: Haskell2010
   build-depends:
     array,
-    base       >= 4.4 && < 5,
+    base       >= 4.5 && < 5,
     bytestring >= 0.9,
     deepseq
   exposed-modules:  Data.BloomFilter
@@ -35,6 +50,7 @@
   install-includes: lookup3.h
 
 test-suite tests
+  default-language: Haskell2010
   type:           exitcode-stdio-1.0
   hs-source-dirs: tests
   main-is:        QC.hs
@@ -50,8 +66,4 @@
 
 source-repository head
   type:     git
-  location: git://github.com/bos/bloomfilter.git
-
-source-repository head
-  type:     mercurial
-  location: https://bitbucket.org/bos/bloomfilter
+  location: git://github.com/haskell-pkg-janitors/bloomfilter.git

Reply via email to