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:[EMAIL PROTECTED]
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe