[commit: packages/containers] ghc-head: Add test to validate bitcount implementation using popCount (220be8c)

git at git.haskell.org git at git.haskell.org
Fri Aug 30 13:33:56 CEST 2013


Repository : ssh://git@git.haskell.org/containers

On branch  : ghc-head
Link       : http://git.haskell.org/?p=packages/containers.git;a=commit;h=220be8c8d7a5fbfbd5712a0aaa96a01283d1ad10

>---------------------------------------------------------------

commit 220be8c8d7a5fbfbd5712a0aaa96a01283d1ad10
Author: Nicolas Trangez <ikke at nicolast.be>
Date:   Sat Sep 15 11:17:41 2012 +0200

    Add test to validate bitcount implementation using popCount


>---------------------------------------------------------------

220be8c8d7a5fbfbd5712a0aaa96a01283d1ad10
 tests/intset-properties.hs |   19 +++++++++++++++++++
 1 file changed, 19 insertions(+)

diff --git a/tests/intset-properties.hs b/tests/intset-properties.hs
index 62d7e69..1a97654 100644
--- a/tests/intset-properties.hs
+++ b/tests/intset-properties.hs
@@ -1,4 +1,10 @@
+{-# LANGUAGE CPP #-}
+#if MIN_VERSION_base(4,5,0)
+import Data.Bits ((.&.), popCount)
+import Data.Word (Word)
+#else
 import Data.Bits ((.&.))
+#endif
 import Data.IntSet
 import Data.List (nub,sort)
 import qualified Data.List as List
@@ -59,6 +65,9 @@ main = defaultMainWithOpts [ testCase "lookupLT" test_lookupLT
                            , testProperty "prop_splitMember" prop_splitMember
                            , testProperty "prop_partition" prop_partition
                            , testProperty "prop_filter" prop_filter
+#if MIN_VERSION_base(4,5,0)
+                           , testProperty "prop_bitcount" prop_bitcount
+#endif
                            ] opts
   where
     opts = mempty { ropt_test_options = Just $ mempty { topt_maximum_generated_tests = Just 500
@@ -310,3 +319,13 @@ prop_partition s i = case partition odd s of
 
 prop_filter :: IntSet -> Int -> Bool
 prop_filter s i = partition odd s == (filter odd s, filter even s)
+
+#if MIN_VERSION_base(4,5,0)
+prop_bitcount :: Int -> Word -> Bool
+prop_bitcount a w = bitcount_orig a w == bitcount_new a w
+  where
+    bitcount_orig a0 x0 = go a0 x0
+      where go a 0 = a
+            go a x = go (a + 1) (x .&. (x-1))
+    bitcount_new a x = a + popCount x
+#endif





More information about the ghc-commits mailing list