Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Jonathan Cast

On 10 Jan 2008, at 6:04 AM, Nicholls, Mark wrote:




-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED]
Sent: 10 January 2008 13:36
To: Nicholls, Mark
Cc: Luke Palmer; haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] confusion about 'instance'

Hello Mark,

Thursday, January 10, 2008, 4:25:20 PM, you wrote:

"instance Num a =>> A a"


Mean the same thing as



"instance A (forall a.Num a=>a)"


programmers going from OOP world always forget that classes in  
Haskell

doesn't the same as classes in C++. *implementation* of this instance
require to pass dictionary of Num class along with type. now imagine
the following code:


My confusion is not between OO classes and Haskell classes, but  
exactly

are the members of a Haskell type class...I'd naively believed them to
be types (like it says on the packet!)...but now I'm not so sure.


A type class *is* a set of types.  But, in Haskell, types like  
(forall a. Num a => a) aren't quite first-class feeling.  A typical  
example of an expression of this type might be (3 + 5), but if I say


x :: Double
x = 3 + 5

the compiler won't complain.

Furthermore, if the compiler sees

instance A Double where

somewhere in the code, when it sees foo (3 + 5), for some method foo  
of the class, it may decide to take (3 + 5) :: Double, not (3 + 5) ::  
forall a. Num a => a.  In that case, you'll get the wrong methods  
called:


class A a where
  foo :: a -> String
instance A Double where
  foo x = "Double"
instance A (forall a. Num a => a) where
  foo x = "number"

If the compiler sees the first instance but not the second, then it  
will think that foo (3 + 5) = "Double".  Adding the second will give  
foo (3 + 5) = "number".  Haskell 98's rules for type classes are  
chosen so that legal code never changes its meaning when you add an  
instance (well, this is a bad example --- but the general point is  
sound).  GHC relaxes these rules in quite a few cases, but in this  
one it's easy enough (in GHC) to get a type isomorphic to forall a.  
Num a => a that can be an instance of a type class that GHC hasn't  
bothered relaxing this particular rule.  (And paying the subsequent  
cost in confusion when working code bitrots because somebody added an  
instance somewhere).


jcc

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


RE: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Nicholls, Mark
Someone said something about having 2 instances of the type in the
typeclass.maybe I misinterpreted it.


> -Original Message-
> From: Luke Palmer [mailto:[EMAIL PROTECTED]
> Sent: 10 January 2008 14:12
> To: Nicholls, Mark
> Cc: Bulat Ziganshin; haskell-cafe@haskell.org
> Subject: Re: Re[2]: [Haskell-cafe] confusion about 'instance'
> 
> On Jan 10, 2008 2:04 PM, Nicholls, Mark <[EMAIL PROTECTED]>
wrote:
> > I can translate OO into mathematical logic pretty easily, I was
trying
> > to do the same thing (informally of course) with Haskellbut
things
> > are not quite what they appearnot because of some OO hang up
(which
> > I probably have many)...but because of what "type class" actually
means.
> 
> But you can think of a type class as a set of types!  The problem is
that
> if we allow certain kinds of instances (such as the Foo instance I
gave
> earlier) then the set is allowed to be non-recursive (only recursively
> enumerable), so determining whether a particular type is a member of
it
> would be undecidable.
> 
> Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 2:04 PM, Nicholls, Mark <[EMAIL PROTECTED]> wrote:
> I can translate OO into mathematical logic pretty easily, I was trying
> to do the same thing (informally of course) with Haskellbut things
> are not quite what they appearnot because of some OO hang up (which
> I probably have many)...but because of what "type class" actually means.

But you can think of a type class as a set of types!  The problem is that
if we allow certain kinds of instances (such as the Foo instance I gave
earlier) then the set is allowed to be non-recursive (only recursively
enumerable), so determining whether a particular type is a member of it
would be undecidable.

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


RE: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Nicholls, Mark

> -Original Message-
> From: Bulat Ziganshin [mailto:[EMAIL PROTECTED]
> Sent: 10 January 2008 13:36
> To: Nicholls, Mark
> Cc: Luke Palmer; haskell-cafe@haskell.org
> Subject: Re[2]: [Haskell-cafe] confusion about 'instance'
> 
> Hello Mark,
> 
> Thursday, January 10, 2008, 4:25:20 PM, you wrote:
> 
> "instance Num a =>> A a"
> 
> > Mean the same thing as
> 
> > "instance A (forall a.Num a=>a)"
> 
> programmers going from OOP world always forget that classes in Haskell
> doesn't the same as classes in C++. *implementation* of this instance
> require to pass dictionary of Num class along with type. now imagine
> the following code:

My confusion is not between OO classes and Haskell classes, but exactly
are the members of a Haskell type class...I'd naively believed them to
be types (like it says on the packet!)...but now I'm not so sure.

> 
> f :: A a => a -> a
> 
> f cannot use your instance because it doesn't receive Num dictionary
> of type `a`. it is unlike OOP situation where every object carries the
> generic VMT which includes methods for every class/interface that
> object supports
> 
> as usual, i suggest you to study
> http://haskell.org/haskellwiki/OOP_vs_type_classes
> first and especially two papers mentioned in References there

I have donelearning is not an atomic operationi.e. I can only
believe what I understand...academic papers are especially beyond me at
this point.

I can translate OO into mathematical logic pretty easily, I was trying
to do the same thing (informally of course) with Haskellbut things
are not quite what they appearnot because of some OO hang up (which
I probably have many)...but because of what "type class" actually means.

So you may be right, I think I need to understand more about the
sematics of Haskell...I was hoping to stay (initially) ignorant.

I will try the postscript doc and see if it makes any sense.


> 
> --
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Luke Palmer
On Jan 10, 2008 1:36 PM, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
> Hello Mark,
>
> Thursday, January 10, 2008, 4:25:20 PM, you wrote:
>
> "instance Num a => A a"
>
> > Mean the same thing as
>
> > "instance A (forall a.Num a=>a)"
>
> programmers going from OOP world always forget that classes in Haskell
> doesn't the same as classes in C++. *implementation* of this instance
> require to pass dictionary of Num class along with type. now imagine
> the following code:
>
> f :: A a => a -> a
>
> f cannot use your instance because it doesn't receive Num dictionary
> of type `a`. it is unlike OOP situation where every object carries the
> generic VMT which includes methods for every class/interface that
> object supports

I'm not sure that's a good argument.  It doesn't need a Num dictionary,
it only needs an A dictionary.  That's what it says.  You only need a Num
dictionary in order to construct an A dictionary, which seems perfectly
reasonable.

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


Re[2]: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Bulat Ziganshin
Hello Mark,

Thursday, January 10, 2008, 4:25:20 PM, you wrote:

"instance Num a =>> A a"

> Mean the same thing as

> "instance A (forall a.Num a=>a)"

programmers going from OOP world always forget that classes in Haskell
doesn't the same as classes in C++. *implementation* of this instance
require to pass dictionary of Num class along with type. now imagine
the following code:

f :: A a => a -> a

f cannot use your instance because it doesn't receive Num dictionary
of type `a`. it is unlike OOP situation where every object carries the
generic VMT which includes methods for every class/interface that
object supports

as usual, i suggest you to study 
http://haskell.org/haskellwiki/OOP_vs_type_classes
first and especially two papers mentioned in References there

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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