argument order of functions in Data.Bits

Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk
Thu Apr 7 06:25:18 EDT 2005


"Simon Marlow" <simonmar at microsoft.com> writes:

> >    shiftL 2 . clearBit 7 . setBit 4 . setBit 1
> > 
> > instead of
> >    flip shiftL 2 . flip clearBit 7 . flip setBit 4 . flip setBit 1
> > 
> > or
> >    (`shiftL` 2) . (`clearBit` 7) . (`setBit` 4) . (`setBit` 1)
> 
> On the whole I agree, but I'm inclined against changing this because it
> would break so much code gratuitously.  I vote for just putting this
> down to a small mistake in the original design, and leaving it.  If
> there's overwhelming support for the change of course we'll make it, but
> I doubt there will be.

For what it's worth, the old library NHC.Bits
    http://cvs.haskell.org/cgi-bin/cvsweb.cgi/nhc98/src/prelude/Bit/Bit.hs
implements the 'set' and 'clear' operations with arguments the natural
way round, although the left and right shift have the same order as
Data.Bits and the C language.  I slightly prefer the NHC names ^>>
and ^<< for shifting too, since they are naturally infix.  Henning's
example composition would look like this:

       (^<< 2) . clear 7 . set 4 . set 1

I suppose if you didn't like the names and argument ordering in Data.Bits,
it would be easy enough to layer your own preferred API on top, e.g.

    module My.Bits where
    import qualified Data.Bits
    class Data.Bits a => Bits a where
        shiftL :: Int -> a -> a
        shiftR :: Int -> a -> a
        shiftL = flip Data.Bits.shiftL
        shiftR = flip Data.Bits.shiftR
	... etc

Regards,
    Malcolm


More information about the Libraries mailing list