Proposal: Add hasBitSize to Data.Bits.Bits

Edward Kmett ekmett at gmail.com
Fri Jul 27 22:24:42 CEST 2012


On Fri, Jul 27, 2012 at 3:42 PM, Ian Lynagh <igloo at earth.li> wrote:

> On Fri, Jul 27, 2012 at 03:06:04PM -0400, Edward Kmett wrote:
> > There is currently no way to know whether or not calling
> > Data.Bits.bitSizewill crash your program.
> >
> > I propose extending the Bits class to include:
> >
> > hasBitSize :: Bits b => b -> Bool
> >
> > such that it returns False for Integer and True for the other instances
>
> Can you give an example of a situation in which you would use
> hasBitSize, and do something useful if it returned False?
>

The following can only work if bitSize is well defined.

traverseBits :: (Applicative f, Bits b) => (Bool -> f Bool) -> b -> f b
traverseBits f b = snd . Prelude.foldr step (bitSize b - 1,0) <$> traverse
(f . testBit b) [0 .. bitSize b - 1] where
  step True (n,r) = (n - 1, setBit r n)
  step _    (n,r) = (n - 1, r)

to work around this I've had to use:

traverseBits :: (Applicative f, Bits b) => (Bool -> f Bool) -> b -> f b
traverseBits f b = Prelude.foldr step 0 <$> traverse g bits
  where
    g n      = (,) n <$> f (testBit b n)
    bits     = Prelude.takeWhile hasBit [0..]
    hasBit n = complementBit b n /= b -- test to make sure that
complementing this bit actually changes the value
    step (n,True) r = setBit r n
    step _        r = r

where I'm manually probing each bit to see that changing it changes the
value.

Used with the other combinators in lens the former just crashes when you use

foldMapOf :: ((c -> Const m d) -> a -> Const m b) -> (c -> m) -> a -> m
foldMapOf l f = getConst . l (Const . f)

toListOf :: ((c -> Const [c] d) -> a -> Const [c] b) -> a -> [c]
toListOf l = foldMapOf l return

Now when we use it with an explicit signature both of these can do
reasonable things:

ghci> toListOf traverseBits (5 :: Int)
[True,False,True,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False]

But with defaulting choosing Integer
ghci> toListOf traverseBits 5

the former instance will crash, whereas the latter properly returns an
infinite lazy list

[True,False,True,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,False,...

It would be much nicer not to have to probe using complementBit creating
ever larger temporary integers just to see if the list of valid bit
positions hadn't been exhausted.

Then I could test at the start to know whether I should use [0..] or
[0..bitSize-1] and get away with much less code and much less unnecessary
memory allocation.

-Edward

Would it be better to move bitSize into a separate class?


I don't think so. Ultimately, you should be able to know for every numeric
type if it has a fixed or variable number of bits. In a perfect world 'd
rather just have bitSize return a Maybe that way we don't have to truck
with partial functions in the API.

However, the case for just adding hasBitSize is that it avoids breaking
existing code.


> > since the vast majority of instances are finite, it may be reasonable to
> > set the default definition to
> >
> > hasBitSize _ = False
>
> Did you mean True?
>

Yes


> Either way, I think I would personally prefer not to have a default, so
> that people need to actually check existing instances.


Also perfectly reasonable.

-Edward
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20120727/723b1a43/attachment.htm>


More information about the Libraries mailing list