The Marriage of Heaven and Hell: Type Classes and Bit-Twiddling

Hi: Looking around further for a charming way to count bits, I found a method that is completely inscrutable might be very fast. http://graphics.stanford.edu/~seander/bithacks.html Counting bits set in 12, 24, or 32-bit words using 64-bit instructions I thought it would be neat to have size function constrained to members of Bounded that would automatically choose which method depending on the extent of the domain of the set. So, a small set could be computed by the very fast method and the compiler would be able to do the dispatch as part of constant folding. This is what I came up with. It works, but it seems kind of forced. I wonder if there is a better way. sizeB :: (Bounded a,Enum a) => a -> Set a -> Int sizeB e = case fromEnum $ maxBound `asTypeOf` e of x | x <= 12 -> \(Set w) -> fromIntegral $ c12 $ fromIntegral w x | x <= 24 -> \(Set w) -> fromIntegral $ c24 $ fromIntegral w x | x <= 32 -> \(Set w) -> fromIntegral $ c32 $ fromIntegral w _ -> \(Set w) -> bitcount 0 w c12 :: Word64 -> Word64 c12 v = (v * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f c24' :: Word64 -> Word64 c24' v = ((v .&. 0xfff) * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f c24 :: Word64 -> Word64 c24 v = (c24' v) + ((((v .&. 0xfff000) `shiftR` 12) * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f) c32 :: Word64 -> Word64 c32 v = (c24 v) + (((v `shiftR` 24) * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f) For example: data Test1 = Foo | Bar | Baaz | Quux deriving (Enum, Bounded) sizeTest1 :: (Set Test1) -> Int sizeTest1 = sizeB Foo Cheers, David -------------------------------- David F. Place mailto:d@vidplace.com

Sorry to respond to my own message, but I found a much more satisfactory way to solve this problem. ghc is able to specialize it so that
data Test1 = Foo | Bar | Baaz | Quux deriving (Enum, Bounded)
sizeTest1 :: (Set Test1) -> Int sizeTest1 = sizeB
compiles into a call directly to size12. I don't think I could do this in any other language (without classes and H&M types.) Hooray for Haskell!
setBound :: Bounded a => Set a -> a setBound s = maxBound
-- | /O(1)/. The number of elements in the set. sizeB :: (Bounded a,Enum a) => Set a -> Int {-# INLINE sizeB #-} sizeB s@(Set w) = case fromEnum $ setBound $ (Set 0) `asTypeOf` s of x | x <= 12 -> fromIntegral $ size12 $ fromIntegral w x | x <= 24 -> fromIntegral $ size24 $ fromIntegral w x | x <= 32 -> fromIntegral $ size32 $ fromIntegral w _ -> fromIntegral $ size64 $ fromIntegral w
size12 :: Word64 -> Word64 size12 v = (v * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f size24' :: Word64 -> Word64 size24' v = ((v .&. 0xfff) * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f size24 :: Word64 -> Word64 size24 v = (size24' v) + ((((v .&. 0xfff000) `shiftR` 12) * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f) size32 :: Word64 -> Word64 size32 v = (size24 v) + (((v `shiftR` 24) * 0x1001001001001 .&. 0x84210842108421) `rem` 0x1f) size64 :: Word64 -> Word64 size64 v = hi + lo where lo = size32 $ v .&. 0xffffffff hi = size32 $ v `shiftR` 32
-------------------------------- David F. Place mailto:d@vidplace.com
participants (1)
-
David F. Place