[C2hs] bug in C2HSMarsh.extractBitMasks function
Duncan Coutts
duncan.coutts at worc.ox.ac.uk
Mon May 9 07:31:57 EDT 2005
Hi,
> extractBitMasks bits =
> [bm | bm <- [minBound..maxBound], bits `containsBitMask` bm]
Sadly this does not work since [minBound..maxBound] uses succ to
enmerate the flags and the Enum instance that c2hs generates does not
include a definition of succ and the default assumes that the enum is
packed whereas of course for flags it is sparse (only has values for
2^n).
We had this bug in gtk2hs too:
> toFlags :: Flags a => Int -> [a]
> toFlags n = andNum n minBound
> where
> andNum n m = (if (n .|. fromEnum m) == n then (m:) else id)
> (if fromEnum m==fromEnum (maxBound `asTypeOf` m) then [] else andNum n (succ m))
We changed this to:
> toFlags :: Flags a => Int -> [a]
> toFlags f = testBits f 1
> where testBits f n
> | f == 0 = []
> | f `testBit` 0 = toEnum n : testBits (f `shiftR` 1) (n `shiftL` 1)
> | otherwise = testBits (f `shiftR` 1) (n `shiftL` 1)
So, extractBitMasks needs fixing, probably in a similar way.
Duncan
More information about the C2hs
mailing list