Proposal: Remove Num superclass of Bits

Daniel Fischer daniel.is.fischer at googlemail.com
Sun Oct 16 02:56:53 CEST 2011


On Sunday 16 October 2011, 02:33:58, Bas van Dijk wrote:
> However having zero and one as methods almost brings us overloaded
> booleans. In that regard it would be better to name them false and
> true though. Ideally we would split Bits into:
> 
> class Boolean b where
>   false :: b
>   true :: b
> 
>   -- Nice in combination with RebindableSyntax:
>   ifThenElse :: b -> a -> a -> a
> 
>   -- Probably does not have to be a method:
>   not :: b -> b
>   not b = ifThenElse b false true
> 
>   (.&.) :: b -> b -> b
>   x .&. y = ifThenElse x (ifThenElse y true) false
> 
>   (.|.) :: b -> b -> b
>   x .|. y = ifThenElse x true (ifThenElse y true false)
> 
> The Bits class then becomes:
> 
> class Boolean b => Bits b where
>   the (.&.), (.|.) are removed because they are defined in Boolean.

I don't like that.

instance Boolean Int where ???

The default methods for (.&.), (.|.) and not would yield quite surprising 
behaviour. And Int shouldn't be a member of class Boolean anyway.

> 
> But an important question is: is it wise to treat booleans and bits
> equally?

IMO, it isn't.

> Because this would allow something like:
> 
> {-# LANGUAGE RebindableSyntax #-}
> 
> foo = if 1 then 2 else 3

Yech!



More information about the Libraries mailing list