Skip to content

Commit

Permalink
Remove bitcount; use popCount directly (#1031)
Browse files Browse the repository at this point in the history
  • Loading branch information
meooow25 authored Aug 31, 2024
1 parent 41005b5 commit e3bd02d
Show file tree
Hide file tree
Showing 3 changed files with 3 additions and 29 deletions.
1 change: 0 additions & 1 deletion containers-tests/tests/IntSetValidity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ import Data.IntSet.Internal
import Data.List (intercalate)
import Numeric (showHex)
import Test.Tasty.QuickCheck (Property, counterexample, property, (.&&.))
import Utils.Containers.Internal.BitUtil (bitcount)

{--------------------------------------------------------------------
Assertions
Expand Down
2 changes: 1 addition & 1 deletion containers/src/Data/IntSet/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -367,7 +367,7 @@ size :: IntSet -> Int
size = go 0
where
go !acc (Bin _ l r) = go (go acc l) r
go acc (Tip _ bm) = acc + bitcount 0 bm
go acc (Tip _ bm) = acc + popCount bm
go acc Nil = acc

-- | \(O(\min(n,W))\). Is the value a member of the set?
Expand Down
29 changes: 2 additions & 27 deletions containers/src/Utils/Containers/Internal/BitUtil.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash #-}
#endif
#if !defined(TESTING) && defined(__GLASGOW_HASKELL__)
{-# LANGUAGE Safe #-}
#endif
Expand Down Expand Up @@ -31,38 +28,16 @@
-- closely.

module Utils.Containers.Internal.BitUtil
( bitcount
, highestBitMask
( highestBitMask
, shiftLL
, shiftRL
, wordSize
) where

import Data.Bits (popCount, unsafeShiftL, unsafeShiftR
import Data.Bits (unsafeShiftL, unsafeShiftR
, countLeadingZeros, finiteBitSize
)


{----------------------------------------------------------------------
[bitcount] as posted by David F. Place to haskell-cafe on April 11, 2006,
based on the code on
http://graphics.stanford.edu/~seander/bithacks.html#CountBitsSetKernighan,
where the following source is given:
Published in 1988, the C Programming Language 2nd Ed. (by Brian W.
Kernighan and Dennis M. Ritchie) mentions this in exercise 2-9. On April
19, 2006 Don Knuth pointed out to me that this method "was first published
by Peter Wegner in CACM 3 (1960), 322. (Also discovered independently by
Derrick Lehmer and published in 1964 in a book edited by Beckenbach.)"
----------------------------------------------------------------------}

bitcount :: Int -> Word -> Int
bitcount a x = a + popCount x
{-# INLINE bitcount #-}

-- The highestBitMask implementation is based on
-- http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2
-- which has been put in the public domain.

-- | Return a word where only the highest bit is set.
highestBitMask :: Word -> Word
highestBitMask w = shiftLL 1 (wordSize - 1 - countLeadingZeros w)
Expand Down

0 comments on commit e3bd02d

Please sign in to comment.