Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-06-26 Thread Edward Kmett
Agreed. I wound up having to add a horrible Num instance for Bool in
'monoids' in order to support a decent Boolean Ring type.

http://comonad.com/haskell/monoids/dist/doc/html/monoids/Data-Ring-Boolean.html

I would much rather be able to get rid of it!

The only problem with eliminating the constraint is that any code that uses
Bits polymorphically might have to pick up a Num annotation, but I can't see
it being a serious problem.

-Edward Kmett

On Wed, Jun 24, 2009 at 8:13 AM, John Meacham j...@repetae.net wrote:

 On Fri, May 08, 2009 at 04:36:41PM +0200, Stephan Friedrichs wrote:
  When looking for an xor function, I found one in Data.Bits but couldn't
  use it for Bool, because Bool is no instance of Bits and of Num (which
  would be necessary, because it's class (Num b) = Bits b). My question
  is: Why not?

 This has bothered me too. However, I think the root problem is that
 'Num' is a superclass of 'Bits'. There is no reason it should be, all
 the default instances can be specified without the Num dependency.

John

 --
 John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
  ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-06-24 Thread John Meacham
On Fri, May 08, 2009 at 04:36:41PM +0200, Stephan Friedrichs wrote:
 When looking for an xor function, I found one in Data.Bits but couldn't
 use it for Bool, because Bool is no instance of Bits and of Num (which
 would be necessary, because it's class (Num b) = Bits b). My question
 is: Why not?

This has bothered me too. However, I think the root problem is that
'Num' is a superclass of 'Bits'. There is no reason it should be, all
the default instances can be specified without the Num dependency.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-09 Thread Stephan Friedrichs
Neil Mitchell wrote:
 
 [...]
 
 Which is a shame, having Bits on Bool seems entirely logical, having
 Num a superclass of Bits seems a little less clear.
 

There are two default implementations in Bits

bit i = 1 `shiftL` i
x `testBit` i = (x .. bit i) /= 0

which rely on Num (and on the fact that 0 ~= 0..0 and 1 ~= 0..01, which
doesn't have to be the case in all Num instances?). But is that worth
having Num as superclass? When declaring in instance for Bits you have
to implement at least 8 functions anyway so these two IMHO don't really
make a difference, do they?

//Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Deniz Dogan
2009/5/8 Stephan Friedrichs deduktionstheo...@web.de:
 Hi!

 When looking for an xor function, I found one in Data.Bits but couldn't
 use it for Bool, because Bool is no instance of Bits and of Num (which
 would be necessary, because it's class (Num b) = Bits b). My question
 is: Why not?

 We could declare

 instance Num Bool where
    (+) False = id
    (+) True  = not

    (*) True  True = True
    (*) _     _    = False

    (-) = (+)

    negate      = id
    abs         = id
    signum      = const True
    fromInteger = not . even

 which basically implements the field with 2 elements and

 instance Bits Bool where
    bitSize  = const 1
    isSigned = const False

    (..) = ()
    (.|.) = (||)
    xor   = (+)

    complement = not

    shift  = const
    shiftL = const
    shiftR = const

    rotate  = const
    rotateL = const
    rotateR = const

    bit = (==0)

    setBit _ 0 = True
    setBit b _ = b

    clearBit _ 0 = False
    clearBit b _ = b

    complementBit b 0 = not b
    complementBit b _ = b

    testBit b 0 = b
    testBit _ _ = False

 quite trivial... Why is this not part of base? Or am I missing something?

 //Stephan

Isn't XOR for booleans (/=)?

Deniz Dogan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Stephan Friedrichs
Deniz Dogan wrote:
 instance Num Bool where
(+) False = id
(+) True  = not

(*) True  True = True
(*) _ _= False

 
 Isn't XOR for booleans (/=)?

Oh right. And (*) would be ():

instance Num Bool where
(+) = (/=)
(*) = ()
-- ...

//Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Sittampalam, Ganesh
Stephan Friedrichs wrote:

 When looking for an xor function, I found one in Data.Bits but
 couldn't use it for Bool, because Bool is no instance of Bits and of
 Num (which would be necessary, because it's class (Num b) = Bits
 b). My question is: Why not?  
 
 [...]
 quite trivial... Why is this not part of base? Or am I missing
 something? 

One reason would be that we don't want 1 + True to typecheck, even if it
does have a sensible interpretation.

Ganesh

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Andrew Wagner
Err, I'm not seeing the danger of this
(+) :: forall a. (Num a) = a - a - a

Doesn't this require the two parameters to be the same instance of Num?

On Fri, May 8, 2009 at 10:51 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:

 Stephan Friedrichs wrote:

  When looking for an xor function, I found one in Data.Bits but
  couldn't use it for Bool, because Bool is no instance of Bits and of
  Num (which would be necessary, because it's class (Num b) = Bits
  b). My question is: Why not?
 
  [...]
  quite trivial... Why is this not part of base? Or am I missing
  something?

 One reason would be that we don't want 1 + True to typecheck, even if it
 does have a sensible interpretation.

 Ganesh


 ===
  Please access the attached hyperlink for an important electronic
 communications disclaimer:
  http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html

  
 ===

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Andrew Wagner
Hmm, I never knew that. Is that a GHC thing? Is it strictly necessary? Seems
like it could be done in the Num instance for Integers, Ints, etc.

On Fri, May 8, 2009 at 11:51 AM, Neil Mitchell ndmitch...@gmail.com wrote:

  Err, I'm not seeing the danger of this
  (+) :: forall a. (Num a) = a - a - a
  Doesn't this require the two parameters to be the same instance of Num?

 I didn't at first, then I remembered:

 1 + True
 =
 fromInteger 1 + True

 And if we have Num for Bool, it type checks.

 Thanks

 Neil

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Neil Mitchell
Nope, it's in the Haskell standard. It means we can type:

1 + (2 :: Int) and have it work

Otherwise what type would 1 have? Integer? Float? It's just a way of
giving constants the type :: Num a = a

On Fri, May 8, 2009 at 4:53 PM, Andrew Wagner wagner.and...@gmail.com wrote:
 Hmm, I never knew that. Is that a GHC thing? Is it strictly necessary? Seems
 like it could be done in the Num instance for Integers, Ints, etc.

 On Fri, May 8, 2009 at 11:51 AM, Neil Mitchell ndmitch...@gmail.com wrote:

  Err, I'm not seeing the danger of this
  (+) :: forall a. (Num a) = a - a - a
  Doesn't this require the two parameters to be the same instance of Num?

 I didn't at first, then I remembered:

 1 + True
 =
 fromInteger 1 + True

 And if we have Num for Bool, it type checks.

 Thanks

 Neil


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Neil Brown

Neil Mitchell wrote:

I didn't at first, then I remembered:

1 + True
=
fromInteger 1 + True

And if we have Num for Bool, it type checks.
  

Does that also mean that you could write:

if 3 - 4 then ... else ...  (= if (fromInteger 3 :: Bool) - (fromInteger 
4 :: Bool) then ... else ...)


or perhaps (not sure if type defaulting stretches to this):

if 1 then ... else ...  (= if (fromInteger 1 :: Bool) then ... else ...)

If you change fromInteger in Num Bool to be fromInteger x = x /= 0, then 
we could all start writing nasty C-like if-expressions...


Thanks,

Neil.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Neil Mitchell
 Err, I'm not seeing the danger of this
 (+) :: forall a. (Num a) = a - a - a
 Doesn't this require the two parameters to be the same instance of Num?

I didn't at first, then I remembered:

1 + True
=
fromInteger 1 + True

And if we have Num for Bool, it type checks.

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Neil Mitchell
 Does that also mean that you could write:

 if 3 - 4 then ... else ...  (= if (fromInteger 3 :: Bool) - (fromInteger 4
 :: Bool) then ... else ...)

No. 3 - 4 is an Integer, the proposal is to convert Bools to Ints, not
Ints to Bools. Of course, Lennart has been asking for precisely this
functionality (overloaded Booleans) for some time - so one day it may
be possible!

You could however do:

if 3 then ... else ..

 If you change fromInteger in Num Bool to be fromInteger x = x /= 0, then we
 could all start writing nasty C-like if-expressions...

Yeah, the more people give examples of the power of Num Bool, the more
it seems like a very bad idea!

Which is a shame, having Bits on Bool seems entirely logical, having
Num a superclass of Bits seems a little less clear.

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread John Dorsey
  Does that also mean that you could write:
 
  if 3 - 4 then ... else ...  (= if (fromInteger 3 :: Bool) - (fromInteger 4
  :: Bool) then ... else ...)
 
 No. 3 - 4 is an Integer, the proposal is to convert Bools to Ints, not
 Ints to Bools.

Rather, (3 - 4) is a (Num t) = t, so yes, this would work with instance
Num Bool.

  *Main if 3 - 4 then yessirree else yep
  yep

 Yeah, the more people give examples of the power of Num Bool, the more
 it seems like a very bad idea!

+1

John

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Brandon S. Allbery KF8NH

On May 8, 2009, at 12:00 , Neil Brown wrote:
If you change fromInteger in Num Bool to be fromInteger x = x /= 0,  
then we could all start writing nasty C-like if-expressions...



I'd be strongly tempted to say

 fromInteger = const False

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Daniel Fischer
Am Freitag 08 Mai 2009 19:18:37 schrieb Brandon S. Allbery KF8NH:
 On May 8, 2009, at 12:00 , Neil Brown wrote:
  If you change fromInteger in Num Bool to be fromInteger x = x /= 0,
  then we could all start writing nasty C-like if-expressions...

 I'd be strongly tempted to say

   fromInteger = const False

fromInteger _ = unsafePerformIO $ randomRIO (False,True)

looks safer to me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe