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:[EMAIL PROTECTED]

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to