Proposal: Remove Num superclass of Bits

Bas van Dijk v.dijk.bas at gmail.com
Mon Oct 17 19:29:07 CEST 2011


I agree.

We should then also drop the default implementation of popCount.

What about adding and exporting helper functions like Ian mentioned:

numBit :: (Bits a, Num a) => Int -> a
numBit i = 1 `shiftL` i
{-# INLINE numBit #-}

numPopCount :: (Bits a, Num a) => a -> Int
numPopCount = go 0
  where
    go !c 0 = c
    go c w = go (c+1) (w .&. w - 1)

numTestBit ::  (Bits a, Num a) => a -> Int -> Bool
x `numTestBit` i = (x .&. bit i) /= 0
{-# INLINE numTestBit #-}

Not sure about the names though?

On 17 October 2011 19:12, Edward Kmett <ekmett at gmail.com> wrote:
> I have to admit this seems to be the most sensible solution, and avoids
> stealing names that are more appropriate for numeric instances anyways.
> -Edward
>
> On Mon, Oct 17, 2011 at 3:26 AM, Joachim Breitner <mail at joachim-breitner.de>
> wrote:
>>
>> Hi,
>>
>> Am Samstag, den 15.10.2011, 17:41 -0700 schrieb John Meacham:
>> > I would just remove the bit and testBit defalut instances, they seem
>> > like reasonable primitives to be required for an instance.
>>
>> I agree. Bits is certainly not something that a Haskell Beginner would
>> have to implement every day, but is more likely a task that requires
>> lots of thought and well-written code anyway. Having to implement these
>> two functions as well is not a large burden there.
>>
>> Greetings,
>> Joachim
>>
>> --
>> Joachim "nomeata" Breitner
>>  mail at joachim-breitner.de  |  nomeata at debian.org  |  GPG: 0x4743206C
>>  xmpp: nomeata at joachim-breitner.de | http://www.joachim-breitner.de/
>>
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
>



More information about the Libraries mailing list