[Haskell-cafe] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Nicholls, Mark
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Foo x y | x - y, y - x
 instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made Integer,Integer a member of it...

Something like that anyway

Then I go

 data Bar

 instance Foo Bar x

Error!but I'm think I understand thisI can't claim that Bar,x is a 
member of Foo and Integer,Integer is member of Foo and preserve my functional 
dependencies, because Bar,Integer is now a member of Foo..

Bad programmer...


So how I naively go


 class NotAnInteger a

 instance (NotAnInteger x) = Foo Bar x

I haven't declared integer to be NotAnIntegerso (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of Foo across different 
combinations of types, without them colliding.







CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK  Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Nicholls, Mark
Ah

So it isn't a closed world

So how do I stop my instances clashing?

The x in

instance Foo Bar x

is never intended to be Integer.



Mark Nicholls | Lead broadcast  corporate architect, Programmes  Development 
- Viacom International Media Networks
A: 17-29 Hawley Crescent London NW1 8TT | e: 
nicholls.m...@vimn.commailto:m...@vimn.com T: +44 (0)203 580 2223

[Description: cid:image001.png@01CD488D.9204D030]

From: Tikhon Jelvis [mailto:tik...@jelv.is]
Sent: 05 July 2013 2:08 PM
To: Nicholls, Mark
Cc: haskell-cafe
Subject: Re: [Haskell-cafe] newbie question about Functional dependencies 
conflict between instance declarations:.


You're running into the open worldassumption--anybody could come along and 
make Integer part of your NotAnInteger class, and there's nothing you can do to 
stop them. This is a design tradeoff for typeclasses: typeclass instances are 
always global and are exported to all other modules you use. This means you 
cannot ensure a type is *not* part of a typeclass. (Or, at the very least, you 
can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow 
question: http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, Nicholls, Mark 
nicholls.m...@vimn.commailto:nicholls.m...@vimn.com wrote:
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Foo x y | x - y, y - x
 instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made Integer,Integer a member of it...

Something like that anyway

Then I go

 data Bar

 instance Foo Bar x

Error!but I'm think I understand thisI can't claim that Bar,x is a 
member of Foo and Integer,Integer is member of Foo and preserve my functional 
dependencies, because Bar,Integer is now a member of Foo..

Bad programmer...


So how I naively go


 class NotAnInteger a

 instance (NotAnInteger x) = Foo Bar x

I haven't declared integer to be NotAnIntegerso (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of Foo across different 
combinations of types, without them colliding.









CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK  Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

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

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100

RE: [Haskell-cafe] type questions again....

2008-01-12 Thread Nicholls, Mark
Is my problem here, simply that the forall extension in GHC is 
misleading.that the forall in
 
MkSwizzle :: (forall a. Ord a = [a] - [a]) - Swizzle
 
is not the same beast as the forall in..
 
data Accum a = forall s. MkAccum s (a - s - s) (s - a)

really
 
data Accum a = exists s. MkAccum s (a - s - s) (s - a)

would be much better syntax
 
don't get me wrongI still don't especially understand...but if it's a 
misleading label...I can mentally substitute exists whenever I see a forall 
without a =.



From: Luke Palmer [mailto:[EMAIL PROTECTED]
Sent: Fri 11/01/2008 18:03
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] type questions again



On Jan 11, 2008 5:47 PM, Nicholls, Mark [EMAIL PROTECTED] wrote:
  If you wrap an existential type up in a constructor, not
  much changes:

 If you wrap a what?should this read existential or universal?

Whoops, right, universal.

   newtype ID = ID (forall a. a - a)
 
  ID can hold any value of type forall a. a - a; i.e. it can hold any
  value which exhibits the property that it can give me a value of type
  a - a for any type a I choose.  In this case the only things ID can
  hold are id and _|_, because id is the only function that has that
  type.   Here's how I might use it:

 It's the only function you've defined the type of

 Id2 :: forall a. a - a

 Now it can hold id2?

Well, that's not what I meant, but yes it can hold id2.

What I meant was that, in this case, id2 = _|_ or id2 = id, there are no
other possibilities.


   id' :: forall a. Num a = a - a
   id' = id  -- it doesn't have to use the constraint if it doesn't
 want to

 it doesn't have to use the constraint if it doesn't want to ?

 If id was of type..

 Id::forall a. Ord a = a - a

 Then I assume it would complain?

Yes.

  but you need to use constructors to use
  them.  I'll write them using GADTs, because I think they're a lot
  clearer that way:
 
  data NUM' where
  NUM' :: Num a = a - NUM'
 
  Look at the type of the constructor NUM'.  It has a universal type,
  meaning whatever type a you pick (as long as it is a Num), you can
  create a NUM' value with it.

 yes

 and then it goes wrong...

  So the type contained inside the NUM'
  constructor

 ?

  is called existential (note that NUM' itself is just a
  regular ADT; NUM' is not existential).
 

 Why existentialsee below...I have a guess

Okay, I was being handwavy here.  Explaining this will allow me to
clear this up.

If you take the non-GADT usage of an existential type:

data Foo
= forall a. Num a = Foo a

That is isomorphic to a type:

data Foo
= Foo (exists a. Num a = a)

Except GHC doesn't support a keyword 'exists', and if it did, it would only be
able to be used inside constructors like this (in order for inference
to be decidable),
so why bother?  That's what I meant by the type inside the constructor, Foo is
not existential, (exists a. Num a = a) is.

  So when you have:
 
   negNUM' :: NUM' - NUM'
   negNUM' (NUM' n) = NUM' (negate n)

Here n has an existential type, specifically (exists a. Num a = a).

  Here the argument could have been constructed using any numeric type
  n, so we know very little about it.  The only thing we know is that it
  is of some type a, and that type has a Num instance.

 I think one of the harrowing things about Haskell is the practice of
 overloading data constructors with type namesit confuses the hell
 out of me

Yeah that took a little getting used to for me too.  But how am I supposed
to come up with enough names if I want to name them differently!?  That
would require too much creativity...  :-)

 OK so this declaration says that forall x constructed using NUM'
 n...there *exists* a type T s.t. T is a member of type class NUM...

(you probably meant type class Num here)

 which in term implies that that there exists the function negate...

 yes?

Huh, I had never thought of it like that, but yes.

I just realized that I think of programming in a way quite different
than I think of logic.  Maybe I should try to have my brain unify them.

   doubleNUM' :: NUM' - NUM'
   doubleNUM' (NUM' n) = NUleM' (n + n)
 
  We can add it to itself, but note:
 
   addNUM' :: NUM' - NUM' - NUM'
   addNUM' (NUM' a) (NUM' b) = NUM (a + b)  -- Illegal!
 
  We can't add them to each other, because the first argument could have
  been constructed with, say, a Double and the other with a Rational.
 
  But do you see why we're allowed to add it to itself?

 We can add it to itself because + is of type a-a-a...

Yep, so whatever type a n happens to have, it matches both arguments.

  How about this:
 
   data Variant where
  Variant :: a - Variant
 
  This is a type that can be constructed with any value whatsoever.
  Looks pretty powerful... but it isn't.  Why not?
 

 Eeek.

 Because a could be of any type whatsover?...so how I actually do
 anything with it?

Right.

Luke

[Haskell-cafe] type questions again....

2008-01-11 Thread Nicholls, Mark
Can someone explain (in simple terms) what is meant by existential and
universal types.

 

Preferably illustrating it in terms of logic rather than lambda
calculus.

 

There's plenty of stuff out there on itbut most of it seems double
dutch (no offense to the dutch intended).

 

 

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


RE: [Haskell-cafe] type questions again....

2008-01-11 Thread Nicholls, Mark


 -Original Message-
 From: Luke Palmer [mailto:[EMAIL PROTECTED]
 Sent: 11 January 2008 17:11
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] type questions again
 
 2008/1/11 Nicholls, Mark [EMAIL PROTECTED]:
  Can someone explain (in simple terms) what is meant by existential
and
  universal types.
 
  Preferably illustrating it in terms of logic rather than lambda
 calculus.
 
 Well, I don't know about logic.  While they are certainly related to
 existential and universal types in logic, I don't really see a way to
 explain them in terms of that.
 
 Universal types are easy, you use them every day in Haskell.  Take for
 example id:
 
  id :: a - a
 
 Or better illustrated (using ghc extension):
 
  id :: forall a. a - a
 
 That means that for any type a I pick, I can get a value of type a -
 a from id.  

Yepit's universal because forall types a.

 If you wrap an existential type up in a constructor, not
 much changes:

If you wrap a what?should this read existential or universal?

 
  newtype ID = ID (forall a. a - a)
 
 ID can hold any value of type forall a. a - a; i.e. it can hold any
 value which exhibits the property that it can give me a value of type
 a - a for any type a I choose.  In this case the only things ID can
 hold are id and _|_, because id is the only function that has that
 type.   Here's how I might use it:

It's the only function you've defined the type of

Id2 :: forall a. a - a

Now it can hold id2?

 
  applyID :: ID - (Int,String) - (Int,String)
  applyID (ID f) (i,s) = (f i, f s)
 
 Note how I can use f, which is a universal type, on both an Int and a
 String in the same place.

Yep.

 
 You can also put typeclass constraints on universals.  Take the
 universal type forall a. Num a = a - a.  Among functions that have
 this type are:
 
  add1 :: forall a. Num a = a - a
  add1 x = x + 1
 
  id' :: forall a. Num a = a - a
  id' = id  -- it doesn't have to use the constraint if it doesn't
want to

it doesn't have to use the constraint if it doesn't want to ?

If id was of type..

Id::forall a. Ord a = a - a

Then I assume it would complain?


 
 Wrapping this up in a constructor:
 
  newtype NUM = NUM (forall a. Num a = a - a)
 
 We can create values:
 
  NUM add1 :: NUM
  NUM id   :: NUM
 
 And use them:
 
  applyNUM :: NUM - (Int, Double) - (Int, Double)
  applyNUM (NUM f) (i,d) = (f i, f d)
 

Yep.

 
 
 Existential types are dual, 

Dual? (like a dual basis rather than double?)

 but you need to use constructors to use
 them.  I'll write them using GADTs, because I think they're a lot
 clearer that way:
 
 data NUM' where
 NUM' :: Num a = a - NUM'
 
 Look at the type of the constructor NUM'.  It has a universal type,
 meaning whatever type a you pick (as long as it is a Num), you can
 create a NUM' value with it.  

yes

and then it goes wrong...

 So the type contained inside the NUM'
 constructor 

?

 is called existential (note that NUM' itself is just a
 regular ADT; NUM' is not existential).
 

Why existentialsee below...I have a guess
 
 So when you have:
 
  negNUM' :: NUM' - NUM'
  negNUM' (NUM' n) = NUM' (negate n)
 
 Here the argument could have been constructed using any numeric type
 n, so we know very little about it.  The only thing we know is that it
 is of some type a, and that type has a Num instance.  

I think one of the harrowing things about Haskell is the practice of
overloading data constructors with type namesit confuses the hell
out of me

OK so this declaration says that forall x constructed using NUM'
n...there *exists* a type T s.t. T is a member of type class NUM...
which in term implies that that there exists the function negate...

yes?

It's existential...because the word exists occurred in the above
translation.


 So we can
 perform operations to it which work for any Num type, such as negate,
 but not things that only work for particular Num types, such as div.

Because the existence of the value implies the existence of a type in
the typeclass?

 
  doubleNUM' :: NUM' - NUM'
  doubleNUM' (NUM' n) = NUleM' (n + n)
 
 We can add it to itself, but note:
 
  addNUM' :: NUM' - NUM' - NUM'
  addNUM' (NUM' a) (NUM' b) = NUM (a + b)  -- Illegal!
 
 We can't add them to each other, because the first argument could have
 been constructed with, say, a Double and the other with a Rational.
 
 But do you see why we're allowed to add it to itself?

We can add it to itself because + is of type a-a-a...

I think

 
 How about this:
 
  data Variant where
 Variant :: a - Variant
 
 This is a type that can be constructed with any value whatsoever.
 Looks pretty powerful... but it isn't.  Why not?
 

Eeek.

Because a could be of any type whatsover?...so how I actually do
anything with it?

Don't know complete guess really.

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

[Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Nicholls, Mark
Should be straight forwardsimplest example is...

class A a

data D = D1

instance A D

fine.D is declared to be a member of type class A

what about.

class A a

type T = (forall x.Num x=x)

instance A T

error!...

 Illegal polymorphic or qualified type: forall x. (Num x) = x
In the instance declaration for `A T'

I am simply trying to state that all members of typeclass Num are of
typeclass A

Doesn't like it.

Does this mean that instance only operates on 'atomic' (for want of a
better word) types?


-Original Message-
From: Peter Verswyvelen [mailto:[EMAIL PROTECTED] On Behalf Of
Peter Verswyvelen
Sent: 03 January 2008 12:02
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

Hi Mark,

 foo1 :: Int - obj - String
 Yep...I think that's what I'd dothough I would have done...
 foo1 :: obj - Int - String
 Does that matter?

Well, it's a good habit in Haskell to move the most important
parameter to
the end of the argument list. See e.g.
http://www.haskell.org/haskellwiki/Parameter_order. 

 OK but I was going to go onto 
 Interface IXA where A : IXA {}
 and
 Interface IXA,B where A : B {}

No, I would not know how to that in Haskell using type classes. It seems
Haskell does not allow cycles in type class definitions. But as I'm new,
this does not mean it's not possible. It's more important to know *what*
you
are trying to do, than to give a solution in a different language, since
OO
and FP are kind of orthogonal languages.

 Where I cannot see a way to do the above in Haskell at allas
 interfaces effectively operator on type classes not typeswhich
seems
 inherently more powerful

Yeah, kind of makes sense. I liked interfaces in C# a lot, but when I
started doing everything with interfaces, I found the lack of support
for
mixins or default implementations problematic. This ended up in a
lot of
copy/paste or encapsulating the implementations into a static class with
plain functions, a mess.

 But if these could be done in Haskell the see what could be made of
 stuff likewhich is obviously problematic in C# it obviously
doesn't
 workbut potentially does make 'sense'.
 Interface IXA : A {}

Ah! That's one of the bigger restrictions in C# yes! C++ can do that;
ATL
uses it a lot, and I also like that approach. You can emulate mixins
with
that, and still stay in the single inheritance paradigm. In Haskell you
don't do that at all of course, since you avoid thinking about objects
and
inheritance in the first place.

OO is strange. They offer you the nice concept of inheritance, and then
the
guidelines tell you: don't use too many levels of inheritance...
Although
I've build huge projects using OO, it always felt a bit like unsafe
hacking.
I don't really have that feeling with Haskell, but that could also be
because I'm too new to the language ;-)

 I'm looking at Haskell because of the formality of it's type
 systembut I'm actually not convinced it is as powerful as an OO
 onei.e. OO ones operatate principally (in Haskell speak) on type
 classes not types

Maybe you are right, I don't know, my theoritical skills are not high
enough
to answer that. Haskell just feels better to me, although the lack of
a
friendly productive IDE and large standard framework remains a bit of a
burden.

Good luck,
Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: Wednesday, January 02, 2008 5:41 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Is there anyone out there who can translate C#
generics into Haskell?

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
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] confusion about 'instance'....

2008-01-10 Thread Nicholls, Mark
Thanks for your response, I think you helped me on one of my previous
abberations.

Hmmmthis all slightly does my head inon one hand we have
typesthen type classes (which appear to be a relation defined on
types)then existential types...which now appear not to be treated
quite in the same way as 'normal' typesand in this instance the
syntax even seems to changedoes 

instance Num a = A a

Mean the same thing as

instance A (forall a.Num a=a)

seems like a weird questions, as you're saying my version doesn't mean
anythingbut

does it mean that forall types 'a', if 'a' is a member of the class
Num, then 'a' is a member of class 'A'

and secondly in what way can this construct lead to undecidable
instances

What are the instances, and what about them is undecidableseems
pretty decidable to me?

What is the ramifications of turning this option on?


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

On Jan 10, 2008 1:03 PM, Nicholls, Mark [EMAIL PROTECTED] wrote:
 Should be straight forwardsimplest example is...

 class A a

 data D = D1

 instance A D

 fine.D is declared to be a member of type class A

 what about.

 class A a

 type T = (forall x.Num x=x)

 instance A T

 error!...

  Illegal polymorphic or qualified type: forall x. (Num x) = x
 In the instance declaration for `A T'

 I am simply trying to state that all members of typeclass Num are of
 typeclass A

Ahh, you want:

  instance Num a = A a

Sorry to lead you on, but that actually is not legal (and
-fallow-undecidable-instances
will make it legal, but you don't want that, because instances of this
particular form
are very likely to lead to an infinite loop).

Adding supertypes like this is not possible in Haskell.  I really want
it to be, but alas...

Luke

 Doesn't like it.

 Does this mean that instance only operates on 'atomic' (for want of a
 better word) types?


 -Original Message-
 From: Peter Verswyvelen [mailto:[EMAIL PROTECTED] On Behalf Of
 Peter Verswyvelen
 Sent: 03 January 2008 12:02
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: RE: [Haskell-cafe] Is there anyone out there who can
translate
 C# generics into Haskell?

 Hi Mark,

  foo1 :: Int - obj - String
  Yep...I think that's what I'd dothough I would have done...
  foo1 :: obj - Int - String
  Does that matter?

 Well, it's a good habit in Haskell to move the most important
 parameter to
 the end of the argument list. See e.g.
 http://www.haskell.org/haskellwiki/Parameter_order.

  OK but I was going to go onto
  Interface IXA where A : IXA {}
  and
  Interface IXA,B where A : B {}

 No, I would not know how to that in Haskell using type classes. It
seems
 Haskell does not allow cycles in type class definitions. But as I'm
new,
 this does not mean it's not possible. It's more important to know
*what*
 you
 are trying to do, than to give a solution in a different language,
since
 OO
 and FP are kind of orthogonal languages.

  Where I cannot see a way to do the above in Haskell at allas
  interfaces effectively operator on type classes not typeswhich
 seems
  inherently more powerful

 Yeah, kind of makes sense. I liked interfaces in C# a lot, but when I
 started doing everything with interfaces, I found the lack of support
 for
 mixins or default implementations problematic. This ended up in a
 lot of
 copy/paste or encapsulating the implementations into a static class
with
 plain functions, a mess.

  But if these could be done in Haskell the see what could be made of
  stuff likewhich is obviously problematic in C# it obviously
 doesn't
  workbut potentially does make 'sense'.
  Interface IXA : A {}

 Ah! That's one of the bigger restrictions in C# yes! C++ can do that;
 ATL
 uses it a lot, and I also like that approach. You can emulate mixins
 with
 that, and still stay in the single inheritance paradigm. In Haskell
you
 don't do that at all of course, since you avoid thinking about
objects
 and
 inheritance in the first place.

 OO is strange. They offer you the nice concept of inheritance, and
then
 the
 guidelines tell you: don't use too many levels of inheritance...
 Although
 I've build huge projects using OO, it always felt a bit like unsafe
 hacking.
 I don't really have that feeling with Haskell, but that could also be
 because I'm too new to the language ;-)

  I'm looking at Haskell because of the formality of it's type
  systembut I'm actually not convinced it is as powerful as an OO
  onei.e. OO ones operatate principally (in Haskell speak) on
type
  classes not types

 Maybe you are right, I don't know, my theoritical skills are not high
 enough
 to answer that. Haskell just feels better to me, although the lack
of
 a
 friendly productive IDE and large standard framework remains a bit

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

2008-01-10 Thread Nicholls, Mark
  class A a
  type T = (forall x.Num x=x)
  instance A T
 
 type declares a synonym, like #define in C - but working only on
types.
 So, essentially, you wrote

Yep that's fine..

 
 instance A (forall x.Num x = x)
 

Yep

 
 which is not very Haskelly.
 

Hmmm...
 
 
 
  I am simply trying to state that all members of typeclass Num are of
 
  typeclass A
 
 
 You can't do that. 

Because it wont let me...or because it makes no sense?

 But, if there would not be any other instances of A,
 then you don't need it at all, you can just use Num class. And if
there
 are some, for example

Ok but there may beI'm just trying to get my head around Haskells
type system 

 
 data D = D
 
 instance A D
 
 

Yep.

D is a member of A

 
 then it can happen (well, it's unlikely, but possible) that you or
some
 other developer working on your code would declare
 
 instance Num D where ...
 

D is a member of Num

(and I'm assuming that we've gotAll Nums are also members of
Awhich is fine...so far).

So...Num x implies A x
So...D is a member of A

Fine.

 
 
 After that, you would have two instances of A for the type D, one
defined
 explicitly and one derived from the Num instance. 

I would have 2 declarations that D is a member of Aboth consistent.

 That's not a problem for
 this empty class, but if class A is not empty, say
 
 
 
 class A x where a :: x
 
 
 
 then the compiler would be unable to decide which instance (and which
a)
 to choose. So allowing that leads to non-obvious bugs.
 

This slightly bamboozles me. 
I only have 1 type.

If I say my name is mark twice, it doesn't mean I belong to set of
objects called Mark twice 

which makes me think that type classes are not simple relations on types
after allthey appear to be relations on declarations of types being
members of a class.

So in my example...there exists two instances of me claiming my name is
Mark.


 
 
 However, if you trust yourself enough, you can do what you want to in
this
 way:
 
 
 
 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
 
 class A a
 
 instance Num a = A a

Hmmm...OK...

It all seems a little odd
___
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: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Nicholls, Mark
  Thanks for your response, I think you helped me on one of my
previous
  abberations.
 
  Hmmmthis all slightly does my head inon one hand we have
  typesthen type classes (which appear to be a relation defined on
  types)then existential types...which now appear not to be
treated
  quite in the same way as 'normal' typesand in this instance the
  syntax even seems to changedoes
 
  instance Num a = A a
 
  Mean the same thing as
 
  instance A (forall a.Num a=a)
 
 Uh... that second one is pretty much nonsensical to me.  I could
imagine
 it
 meaning the type (forall a.Num a = a) itself is an instance of A, but
not
 specializations of it (like Int).  But without an identity in the type
 system,
 the meaning of that would be convoluted.  It's kind of off topic, but
just
 for the interested, here are two similar, legal constructions:

ok

 
 Existential:
 newtype Numeric  = forall a. Num a = Numeric a
 

My compiler doesn't like this A newtype constructor cannot have an
existential context, 

 Universal:
 newtype Numeric' = Numeric' (forall a. Num a = a)

Not so sure I understand the difference here. 

 
 Both of which are easily declared to be instances of Num.  They're not
 what
 you want though, because Haskell doesn't support what you want :-(.
 Anyway,
 if you have a value of type Numeric, you know it contains some value
of a
 Num type, but you don't know what type exactly (and you can never find
 out).
 If you have a value of type Numeric', then you can produce a value of
any
 Num
 type you please (i.e. the value is built out of only operations in the
Num
 class, nothing more specific).
 
 But that was a digression; ignore at your leisure (now that you've
already
 read it :-).

Makes little sense to meNumeric looks reasonable...I think...
Numeric'...seems weirdand I'm not sure I understood the
explanation.

 
  and secondly in what way can this construct lead to undecidable
  instances
 
 Okay, read:
 
 instance A a = B b
 
 (where a and be might be more complex expressions) not as b is an
 instance of
 B whenever a is an instance of A, but rather as b is an instance of
B,
 and
 using it as such adds a constraint of A a.  Let's look at a slightly
more
 complex (and contrived) example:
 
 class Foo a where
 foo :: a - a
 
 instance (Foo [a]) = Foo a where
 foo x = head $ foo [x]
 
 Then when checking the type of the expression foo (0::Int), we'd have
to
 check if Foo Int, Foo [Int], Foo [[Int]], Foo [[[Int]]], ad infinitum.

Ooo blimeythat sort of makes sense.


 
  What are the instances, and what about them is undecidableseems
  pretty decidable to me?
 
  What is the ramifications of turning this option on?
 
 Theoretically, compile time fails to guarantee to ever finish.
 Practically,
 ghc will give you a very-difficult-to-reason-about message when
constraint
 checking stack overflows.
 
 Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-01-10 Thread Nicholls, Mark


 -Original Message-
 From: Jules Bean [mailto:[EMAIL PROTECTED]
 Sent: 10 January 2008 14:22
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] confusion about 'instance'
 
 Nicholls, Mark wrote:
 
  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.
 
 
 
 Which packet?

The packet labelled type classyou're from .co.ukyou should
understand my English idioms. :-) 

 
 Classes are not types.

Yep.

 
 Classes are groups of types. Sets of types. Classifications of types.

I had them down as an n-ary relation on typessomeone's said
something somewhere that's made me question that...but I think I
misinterpreted themso I may default back to n-ary relation.

 
 For any type, you can ask the quesiton is this type a member of this
 class, or not?

yep

 
 Without wishing to split hairs too finely, I find it a useful
intuition
 not to consider the class context part of the type somehow.
 
 So, when you see this:
 
 (Num a, Eq b) = a - b - a
 
 Rather than thinking of that whole thing as a type, it helps to think
of
 the part on the right of the = as the 'actual type' and the part on
the
 left of the = as some extra constraints on the type.

Hmmm...I'm not sure that helpsit may just make me more confused.

 
 So you might say this has the type a - b - a, providing that a is
a
 Num and b is an Eq.
 
 Jules
___
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[6]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-04 Thread Nicholls, Mark
You may be right...but learning is not an atomic thingwherever I
start I will get strange things happening. 

-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 03 January 2008 18:59
To: Nicholls, Mark
Cc: Bulat Ziganshin; haskell-cafe@haskell.org
Subject: Re[6]: [Haskell-cafe] Is there anyone out there who can
translate C# generics into Haskell?

Hello Mark,

Thursday, January 3, 2008, 6:40:13 PM, you wrote:

it would be hard to understand overlap without knowing both systems.
you will believe that you understand it, but things will go strange
ways :)

 I do not necessarily disagree

 But if I can identify the overlapthen I have leant the
overlap...on
 the cheap.
  
 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 14:39
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[4]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 2:13:08 PM, you wrote:

 of course *some* overlap exists but in order to understand it you
 should know exact shape of both methods

 when i tried to develop complex library without understanding t.c.
 implementation, i constantly goes into the troubles - things that i
 (using my OOP experience) considered as possible, was really
 impossible in Haskell

 so i'm really wonder why you don't want to learn the topic thoroughly


 I loosely do understandbut very looselybut I'm not, as yet,
 convinced it is completely relevant.

 The implementation may differ, but that does not mean that there is
no
 overlapI am not expecting one model to be a superset of the
other,
 but I am expecting some sort of overlap between 'interface'
 implementation and type class instance declaration.


 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 10:54
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 1:22:26 PM, you wrote:

 because they have different models. i recommend you to start from
 learning this model, otherwise you will don't understand how Haskell
 really works and erroneously apply your OOP knowledge to Haskell data
 structures.

 shortly said, there are 3 ways to polymorphism:

 1) C++ templates - type-specific code generated at compile time
 2) OOP classes - every object carries VMT which allows to select
 type-specific operation
 3) type classes - dictionary of type-specific operations is given as
 additional hidden argument to each function

 Haskell uses t.c. and its abilities are dictated by this
 implementation. there is no simple and direct mapping between
 features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would
seem
 to
 describe/construct values/objectsthey may not be equivalent, but
 I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
 translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References










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


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
I was thinking more along type classesand then I was going to throw
some spanners in the works

 



From: Ryan Ingram [mailto:[EMAIL PROTECTED] 
Sent: 02 January 2008 17:41
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

 

Of course it depends what's inside the braces, and what you want to do
with it, but I'd be inclined to do something like this:

 

1) data IX a = IX { constructor :: Int - a, ... }

2) data IX a b = IX { constructor :: Int - b, func :: a - b, ... }

3) data IX a b = IX { iy :: IY a, ... }

4) data IX a b = IX { iz :: IZ b, iy :: IY a, ... }

 

Can you specify more clearly what the goal of the conversion is?  If you
want OO style behavior the thing that is most important is existential
quantification.

 

  -- ryan

 

On 1/2/08, Nicholls, Mark [EMAIL PROTECTED] wrote: 

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1)

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
   Where A : IY
{
}

4)

Interface IXA : IZ
   Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
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] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark

[snip]

-- C#: interface IX1 { String foo1(int); }
class IX1 obj where 
  foo1 :: Int - obj - String

Yep...I think that's what I'd dothough I would have done...

foo1 :: obj - Int - String

Does that matter?


-- C#: interface IX2A { String foo2(A); }
class IX2 obj a where 
  foo2 :: a - obj - String

Ok same here

--C#: interface IX3A where A : IY { String foo3(A); }
class IY a where {- ... -}
class IY a = IX3 obj a where 
  foo3 :: a - obj - String

Yep I think again I would have guessed at that

--C#: interface IX4A : IZ where A : IY
class IZ a where {- ... -}
class (IY a, IZ obj) = IX4 obj a where
  foo4 :: a - obj - String

H...this would have been one of my guessesbut let me have a
go... 

This assumes your objects are immutable, otherwise you would have to
return (obj,String) instead of just String and then you most likely
want to
use the state monad and do notation to make functional programming
look
more like imperative programming.

This is finemy oop is largely immutable.

You really have to drop the OO way of thinking, 
which I find the hardest :)
Haskell's type classes are more powerful in some sense than C#
interfaces;
for example, in C# you can't attach an interface to any class (take for
example the Point struct), it has to be your own class, while in
Haskell,
you can implement an instance of a type class for any datatype!

OK but I was going to go onto 

Interface IXA 
where A : IXA
{
}

And 

Interface IXA,B 
where A : B
{
}

Where I cannot see a way to do the above in Haskell at allas
interfaces effectively operator on type classes not typeswhich seems
inherently more powerful

But if these could be done in Haskell the see what could be made of
stuff likewhich is obviously problematic in C# it obviously doesn't
workbut potentially does make 'sense'.

Interface IXA : A
{
}

Hope this helps a bit. As I'm new myself to Haskell, so take this with
a
grain of salt.

It does...I will have a go with your sample answers.

Once you bite the bullet, I found Haskell a lot more fun than C#,
although
C# of course comes with a gigantic .NET framework and tools...

I'm looking at Haskell because of the formality of it's type
systembut I'm actually not convinced it is as powerful as an OO
onei.e. OO ones operatate principally (in Haskell speak) on type
classes not types

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: Wednesday, January 02, 2008 5:41 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Is there anyone out there who can translate C#
generics into Haskell?

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
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] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
Can you give me a summary of why it's meaningless.both would seem to
describe/construct values/objectsthey may not be equivalent, but I
would expect some considerable overlap.

-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 02 January 2008 20:29
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

Hello Mark,

Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
some

it's meaningless. read
http://haskell.org/haskellwiki/OOP_vs_type_classes
and especially papers mentioned in the References

-- 
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] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
I loosely do understandbut very looselybut I'm not, as yet,
convinced it is completely relevant.

The implementation may differ, but that does not mean that there is no
overlapI am not expecting one model to be a superset of the other,
but I am expecting some sort of overlap between 'interface'
implementation and type class instance declaration.


-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 03 January 2008 10:54
To: Nicholls, Mark
Cc: Bulat Ziganshin; haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
translate C# generics into Haskell?

Hello Mark,

Thursday, January 3, 2008, 1:22:26 PM, you wrote:

because they have different models. i recommend you to start from
learning this model, otherwise you will don't understand how Haskell
really works and erroneously apply your OOP knowledge to Haskell data
structures.

shortly said, there are 3 ways to polymorphism:

1) C++ templates - type-specific code generated at compile time
2) OOP classes - every object carries VMT which allows to select
type-specific operation
3) type classes - dictionary of type-specific operations is given as
additional hidden argument to each function

Haskell uses t.c. and its abilities are dictated by this
implementation. there is no simple and direct mapping between
features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem
to
 describe/construct values/objectsthey may not be equivalent, but I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References




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


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
Ahh ok I see what is meant by the parameter order

-Original Message-
From: Peter Verswyvelen [mailto:[EMAIL PROTECTED] On Behalf Of
Peter Verswyvelen
Sent: 03 January 2008 12:02
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

Hi Mark,

 foo1 :: Int - obj - String
 Yep...I think that's what I'd dothough I would have done...
 foo1 :: obj - Int - String
 Does that matter?

Well, it's a good habit in Haskell to move the most important
parameter to
the end of the argument list. See e.g.
http://www.haskell.org/haskellwiki/Parameter_order. 

 OK but I was going to go onto 
 Interface IXA where A : IXA {}
 and
 Interface IXA,B where A : B {}

No, I would not know how to that in Haskell using type classes. It seems
Haskell does not allow cycles in type class definitions. But as I'm new,
this does not mean it's not possible. It's more important to know *what*
you
are trying to do, than to give a solution in a different language, since
OO
and FP are kind of orthogonal languages.

 Where I cannot see a way to do the above in Haskell at allas
 interfaces effectively operator on type classes not typeswhich
seems
 inherently more powerful

Yeah, kind of makes sense. I liked interfaces in C# a lot, but when I
started doing everything with interfaces, I found the lack of support
for
mixins or default implementations problematic. This ended up in a
lot of
copy/paste or encapsulating the implementations into a static class with
plain functions, a mess.

 But if these could be done in Haskell the see what could be made of
 stuff likewhich is obviously problematic in C# it obviously
doesn't
 workbut potentially does make 'sense'.
 Interface IXA : A {}

Ah! That's one of the bigger restrictions in C# yes! C++ can do that;
ATL
uses it a lot, and I also like that approach. You can emulate mixins
with
that, and still stay in the single inheritance paradigm. In Haskell you
don't do that at all of course, since you avoid thinking about objects
and
inheritance in the first place.

OO is strange. They offer you the nice concept of inheritance, and then
the
guidelines tell you: don't use too many levels of inheritance...
Although
I've build huge projects using OO, it always felt a bit like unsafe
hacking.
I don't really have that feeling with Haskell, but that could also be
because I'm too new to the language ;-)

 I'm looking at Haskell because of the formality of it's type
 systembut I'm actually not convinced it is as powerful as an OO
 onei.e. OO ones operatate principally (in Haskell speak) on type
 classes not types

Maybe you are right, I don't know, my theoritical skills are not high
enough
to answer that. Haskell just feels better to me, although the lack of
a
friendly productive IDE and large standard framework remains a bit of a
burden.

Good luck,
Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: Wednesday, January 02, 2008 5:41 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Is there anyone out there who can translate C#
generics into Haskell?

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
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: Re[4]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
I do not necessarily disagree

But if I can identify the overlapthen I have leant the overlap...on
the cheap.
 
-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 03 January 2008 14:39
To: Nicholls, Mark
Cc: Bulat Ziganshin; haskell-cafe@haskell.org
Subject: Re[4]: [Haskell-cafe] Is there anyone out there who can
translate C# generics into Haskell?

Hello Mark,

Thursday, January 3, 2008, 2:13:08 PM, you wrote:

of course *some* overlap exists but in order to understand it you
should know exact shape of both methods

when i tried to develop complex library without understanding t.c.
implementation, i constantly goes into the troubles - things that i
(using my OOP experience) considered as possible, was really
impossible in Haskell

so i'm really wonder why you don't want to learn the topic thoroughly


 I loosely do understandbut very looselybut I'm not, as yet,
 convinced it is completely relevant.

 The implementation may differ, but that does not mean that there is no
 overlapI am not expecting one model to be a superset of the other,
 but I am expecting some sort of overlap between 'interface'
 implementation and type class instance declaration.


 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 10:54
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 1:22:26 PM, you wrote:

 because they have different models. i recommend you to start from
 learning this model, otherwise you will don't understand how Haskell
 really works and erroneously apply your OOP knowledge to Haskell data
 structures.

 shortly said, there are 3 ways to polymorphism:

 1) C++ templates - type-specific code generated at compile time
 2) OOP classes - every object carries VMT which allows to select
 type-specific operation
 3) type classes - dictionary of type-specific operations is given as
 additional hidden argument to each function

 Haskell uses t.c. and its abilities are dictated by this
 implementation. there is no simple and direct mapping between
 features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem
 to
 describe/construct values/objectsthey may not be equivalent, but
I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
 translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References







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


[Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-02 Thread Nicholls, Mark
I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Nicholls, Mark
Hello, I wonder if someone could answer the following...

The short question is what does @ mean in 

 

mulNat a b

| a = b = mulNat' a b b

| otherwise = mulNat' b a a

where

 mulNat' x@(S a) y orig

 | x == one = y

 | otherwise = mulNat' a (addNat orig y) orig

 

The long version, explaining what everything means is

 

 here's a definition of multiplication on natural numbers I'm reading

 on a blog

 

 data Nat = Z | S Nat

deriving Show

 

 one :: Nat

 one = (S Z)

 

 mulNat :: Nat - Nat - Nat

 mulNat _ Z = Z

 mulNat Z _ = Z

 mulNat a b

| a = b = mulNat' a b b

| otherwise = mulNat' b a a

where

 mulNat' x@(S a) y orig

 | x == one = y

 | otherwise = mulNat' a (addNat orig y) orig

 

 Haskell programmers seem to have a very irritating habit of trying to

 be overly concise...which makes learnign the language extremely

 hard...this example is actually relatively verbosebut anyway...

 

 Z looks like Zero...S is the successor function...Nat are the

 Natural numbers.

 

 mulNat _ Z = Z

 mulNat Z _ = Z

 

 translates to...

 

 x * 0 = 0fine...

 0 * x = 0fine..

 

 mulNat a b

| a = b = mulNat' a b b

| otherwise = mulNat' b a a

where

 mulNat' x@(S a) y orig

 | x == one = y

 | otherwise = mulNat' a (addNat orig y) orig

 

 is a bit more problematic...

 lets take a as 3 and b as 5...

 

 so now we have

 

 mulNat' 3 5 5

 

 but what does the x@(S a) mean? in

 

 mulNat' x@(S a) y orig

 



From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: 21 December 2007 17:47
To: David Menendez
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] nice simple problem for someone
struggling

 

Let me resend the code...as it stands

 

module Main where

 

data SquareType numberType = Num numberType = SquareConstructor
numberType

 

class ShapeInterface shape where

  area :: Num numberType = shape-numberType

 

data ShapeType = forall a. ShapeInterface a = ShapeType a

 

instance (Num a) = ShapeInterface (SquareType a) where 

area (SquareConstructor side) = side * side

 

 

and the errors are for the instance declaration...

 

[1 of 1] Compiling Main ( Main.hs, C:\Documents and
Settings\nichom\Haskell\Shapes2\out/Main.o )

 

Main.hs:71:36:

Couldn't match expected type `numberType' against inferred type `a'

  `numberType' is a rigid type variable bound by

   the type signature for `area' at Main.hs:38:15

  `a' is a rigid type variable bound by

  the instance declaration at Main.hs:70:14

In the expression: side * side

In the definition of `area':

area (SquareConstructor side) = side * side

 

I'm becoming lost in errors I don't comprehend

 

What bamboozles me is it seemed such a minor enhancement.



From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf
Of David Menendez
Sent: 21 December 2007 17:05
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling

 

On Dec 21, 2007 11:50 AM, Nicholls, Mark [EMAIL PROTECTED]
wrote:

Now I have

module Main where

data SquareType numberType = Num numberType = SquareConstructor
numberType


This is a valid declaration, but I don't think it does what you want it
to. The constraint on numberType applies only to the data constructor. 

That is, given an unknown value of type SquareType a for some a, we do
not have enough information to infer Num a.

For your code, you want something like:

instance (Num a) = ShapeInterface (SquareType a) where 
area (SquareConstructor side) = side * side


-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/  

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


RE: [Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Nicholls, Mark
So in the example given...

mulNat a b
 | a = b = mulNat' a b b
 | otherwise = mulNat' b a a
 where
  mulNat' x@(S a) y orig
  | x == one = y
  | otherwise = mulNat' a (addNat orig y) orig

Is equivalent to 

mulNat a b
 | a = b = mulNat' a b b
 | otherwise = mulNat' b a a
 where
  mulNat' (S a) y orig
  | (S a) == one = y
  | otherwise = mulNat' a (addNat orig y) orig

?

-Original Message-
From: Alfonso Acosta [mailto:[EMAIL PROTECTED] 
Sent: 28 December 2007 11:20
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] what does @ mean?.

@ works as an aliasing primitive for the arguments of a function

f x@(Just y) = ...

using x in the body of f is equivalent to use Just y. Perhaps in
this case is not really useful, but in some other cases it saves the
effort and space of retyping really long expressions. And what is even
more important, in case an error is made when choosing the pattern,
you only have to correct it in one place.

On Dec 28, 2007 12:05 PM, Nicholls, Mark [EMAIL PROTECTED]
wrote:




 Hello, I wonder if someone could answer the following...

 The short question is what does @ mean in



 mulNat a b

 | a = b = mulNat' a b b

 | otherwise = mulNat' b a a

 where

  mulNat' x@(S a) y orig

  | x == one = y

  | otherwise = mulNat' a (addNat orig y) orig



 The long version, explaining what everything means is



  here's a definition of multiplication on natural numbers I'm reading

  on a blog



  data Nat = Z | S Nat

 deriving Show



  one :: Nat

  one = (S Z)



  mulNat :: Nat - Nat - Nat

  mulNat _ Z = Z

  mulNat Z _ = Z

  mulNat a b

 | a = b = mulNat' a b b

 | otherwise = mulNat' b a a

 where

  mulNat' x@(S a) y orig

  | x == one = y

  | otherwise = mulNat' a (addNat orig y) orig



  Haskell programmers seem to have a very irritating habit of trying to

  be overly concise...which makes learnign the language extremely

  hard...this example is actually relatively verbosebut anyway...



  Z looks like Zero...S is the successor function...Nat are the

  Natural numbers.



  mulNat _ Z = Z

  mulNat Z _ = Z



  translates to...



  x * 0 = 0fine...

  0 * x = 0fine..



  mulNat a b

 | a = b = mulNat' a b b

 | otherwise = mulNat' b a a

 where

  mulNat' x@(S a) y orig

  | x == one = y

  | otherwise = mulNat' a (addNat orig y) orig



  is a bit more problematic...

  lets take a as 3 and b as 5...



  so now we have



  mulNat' 3 5 5



  but what does the x@(S a) mean? in



  mulNat' x@(S a) y orig



  


 From: [EMAIL PROTECTED]
 [mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
  Sent: 21 December 2007 17:47
  To: David Menendez
  Cc: Jules Bean; haskell-cafe@haskell.org
  Subject: RE: [Haskell-cafe] nice simple problem for someone
struggling



 Let me resend the code...as it stands



 module Main where



 data SquareType numberType = Num numberType = SquareConstructor
numberType



 class ShapeInterface shape where

   area :: Num numberType = shape-numberType



 data ShapeType = forall a. ShapeInterface a = ShapeType a



 instance (Num a) = ShapeInterface (SquareType a) where

 area (SquareConstructor side) = side * side





 and the errors are for the instance declaration...



 [1 of 1] Compiling Main ( Main.hs, C:\Documents and
 Settings\nichom\Haskell\Shapes2\out/Main.o )



 Main.hs:71:36:

 Couldn't match expected type `numberType' against inferred type
`a'

   `numberType' is a rigid type variable bound by

the type signature for `area' at Main.hs:38:15

   `a' is a rigid type variable bound by

   the instance declaration at Main.hs:70:14

 In the expression: side * side

 In the definition of `area':

 area (SquareConstructor side) = side * side



 I'm becoming lost in errors I don't comprehend



 What bamboozles me is it seemed such a minor enhancement.


  


 From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On
Behalf Of
 David Menendez
  Sent: 21 December 2007 17:05
  To: Nicholls, Mark
  Cc: Jules Bean; haskell-cafe@haskell.org
  Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling



 On Dec 21, 2007 11:50 AM, Nicholls, Mark [EMAIL PROTECTED]
wrote:



 Now I have

  module Main where

  data SquareType numberType = Num numberType = SquareConstructor
  numberType



  This is a valid declaration, but I don't think it does what you want
it to.
 The constraint on numberType applies only to the data constructor.

  That is, given an unknown value of type SquareType a for some a, we
do not
 have enough information to infer Num

RE: [Haskell-cafe] what does @ mean?.....

2007-12-28 Thread Nicholls, Mark
Lovelythank you very muchanother small step forward.

-Original Message-
From: Chaddaï Fouché [mailto:[EMAIL PROTECTED] 
Sent: 28 December 2007 11:29
To: Nicholls, Mark
Cc: Alfonso Acosta; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] what does @ mean?.

2007/12/28, Nicholls, Mark [EMAIL PROTECTED]:
 So in the example given...

 mulNat a b
  | a = b = mulNat' a b b
  | otherwise = mulNat' b a a
  where
   mulNat' x@(S a) y orig
   | x == one = y
   | otherwise = mulNat' a (addNat orig y) orig

 Is equivalent to

 mulNat a b
  | a = b = mulNat' a b b
  | otherwise = mulNat' b a a
  where
   mulNat' (S a) y orig
   | (S a) == one = y
   | otherwise = mulNat' a (addNat orig y) orig

 ?

Yes, but in the second version, it has to reconstruct (S a) before
comparing it to one where in the first it could do the comparison
directly. In this cas there may be some optimisation involved that
negate this difference but in many case it can do a real performance
difference.
The as-pattern (@ means as) is both practical and performant in most cases.

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


[Haskell-cafe] translating some C# abstractions into Haskell....

2007-12-28 Thread Nicholls, Mark
Lets say I've got 

Interface IFooX,Y
Where X : IBar
Where Y : IBar
{
}


Would seem to translate roughly to

class (IBar x, IBar y) = IFoo foo x y

? (or does it?)


-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: 28 December 2007 11:30
To: Chaddaï Fouché
Cc: haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] what does @ mean?.

Lovelythank you very muchanother small step forward.

-Original Message-
From: Chaddaï Fouché [mailto:[EMAIL PROTECTED] 
Sent: 28 December 2007 11:29
To: Nicholls, Mark
Cc: Alfonso Acosta; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] what does @ mean?.

2007/12/28, Nicholls, Mark [EMAIL PROTECTED]:
 So in the example given...

 mulNat a b
  | a = b = mulNat' a b b
  | otherwise = mulNat' b a a
  where
   mulNat' x@(S a) y orig
   | x == one = y
   | otherwise = mulNat' a (addNat orig y) orig

 Is equivalent to

 mulNat a b
  | a = b = mulNat' a b b
  | otherwise = mulNat' b a a
  where
   mulNat' (S a) y orig
   | (S a) == one = y
   | otherwise = mulNat' a (addNat orig y) orig

 ?

Yes, but in the second version, it has to reconstruct (S a) before
comparing it to one where in the first it could do the comparison
directly. In this cas there may be some optimisation involved that
negate this difference but in many case it can do a real performance
difference.
The as-pattern (@ means as) is both practical and performant in most cases.

-- 
Jedaï
___
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


[Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
I'm just trying to pick up the basicsand I've managed to write this
code...which remarkably works..

 

 

 

module Main where

 

data SquareType = SquareConstructor Int

 

class ShapeInterface shape where

  area :: shape-Int

 

data ShapeType = forall a. ShapeInterface a = ShapeType a

 

instance ShapeInterface SquareType where

  area (SquareConstructor sideLength) = sideLength * sideLength

 

main = do 

  putStrLn (show (area (SquareConstructor 4)))

  name - getLine

  putStrLn 

 

 

 

But my next iteration was to try to parametise SquareType

 

So something like 

 

data SquareType a = Num a = SquareConstructor a

 

but of course doing this breaks everything...sepecifically the
instance declaration

 

`SquareType' is not applied to enough type arguments

Expected kind `*', but `SquareType' has kind `* - *'

In the instance declaration for `ShapeInterface SquareType'

 

And I can't seem to get it to work.

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


RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
ReallyI'm sure I tried that...(as it seemed obvious) ... and it
failedbut I'll have another go

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: 21 December 2007 15:33
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling

Nicholls, Mark wrote:
 *instance* ShapeInterface SquareType *where*
 
   area (SquareConstructor sideLength) = sideLength * sideLength


 *data* SquareType a = Num a = SquareConstructor a


Now you have changed your type from SquareType to SquareType a, you need

to change the instance to:

instance ShapeInterface (SquareType a) where...


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


RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Now I have

module Main where

data SquareType numberType = Num numberType = SquareConstructor
numberType

data RectangleType = RectangleConstructor Int Int

class ShapeInterface shape where
area :: shape-Int

data ShapeType = forall a. ShapeInterface a = ShapeType a

instance ShapeInterface (SquareType numberType) where
area (SquareConstructor sideLength) = sideLength * sideLength
 
main = do 
putStrLn (show (area (SquareConstructor 4)))
name - getLine
putStrLn 


but get the errors

In the expression: sideLength * sideLength In the definition of `area':
area (SquareConstructor sideLength) = sideLength * sideLength In the
definition for method `area'

And

Couldn't match expected type `Int' against inferred type `numberType'
`numberType' is a rigid type variable bound by  


But to be fairI almost understand the errorswhich is not bad for
me.surely 

class ShapeInterface shape where
area :: shape-Int

now looks dubiousI want it to be something like

class ShapeInterface shape where
area :: Num numberType = shape-Int ?

but my instance declaration still complains with the errors above and I
now get an error in the class declaration

`numberType1' is a rigid type variable bound by

It's slightly doing my head inand reminds me of trying to learn C++
oncenot a pleasant experiencethough I did eventually
succeedto a degree.

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: 21 December 2007 15:33
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling

Nicholls, Mark wrote:
 *instance* ShapeInterface SquareType *where*
 
   area (SquareConstructor sideLength) = sideLength * sideLength


 *data* SquareType a = Num a = SquareConstructor a


Now you have changed your type from SquareType to SquareType a, you need

to change the instance to:

instance ShapeInterface (SquareType a) where...


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


RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Oh

 

You are correct...

 

I thought from 

 

Num numberType = SquareConstructor
numberType

 

We could deduce that (in English rather than get Haskell and FOL
confusion) 

 

all values of SquareConstructor athe type of a would have be be in
class Num?..

is this not correct?if notwhy not? 

 



From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf
Of David Menendez
Sent: 21 December 2007 17:05
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling

 

On Dec 21, 2007 11:50 AM, Nicholls, Mark [EMAIL PROTECTED]
wrote:

Now I have

module Main where

data SquareType numberType = Num numberType = SquareConstructor
numberType


This is a valid declaration, but I don't think it does what you want it
to. The constraint on numberType applies only to the data constructor. 

That is, given an unknown value of type SquareType a for some a, we do
not have enough information to infer Num a.

For your code, you want something like:

instance (Num a) = ShapeInterface (SquareType a) where 
area (SquareConstructor side) = side * side


-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/  

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


RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Yes sorrybut this still fails with

 

`numberType1' is a rigid type variable bound by

 



From: Brent Yorgey [mailto:[EMAIL PROTECTED] 
Sent: 21 December 2007 17:29
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling

 

 


class ShapeInterface shape where
   area :: shape-Int

now looks dubiousI want it to be something like

class ShapeInterface shape where
   area :: Num numberType = shape-Int ?


Rather, I think you probably want

class ShapeInterface shape where
area :: Num numberType = shape - numberType

-Brent

 

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


RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Let me resend the code...as it stands

 

module Main where

 

data SquareType numberType = Num numberType = SquareConstructor
numberType

 

class ShapeInterface shape where

  area :: Num numberType = shape-numberType

 

data ShapeType = forall a. ShapeInterface a = ShapeType a

 

instance (Num a) = ShapeInterface (SquareType a) where 

area (SquareConstructor side) = side * side

 

 

and the errors are for the instance declaration...

 

[1 of 1] Compiling Main ( Main.hs, C:\Documents and
Settings\nichom\Haskell\Shapes2\out/Main.o )

 

Main.hs:71:36:

Couldn't match expected type `numberType' against inferred type `a'

  `numberType' is a rigid type variable bound by

   the type signature for `area' at Main.hs:38:15

  `a' is a rigid type variable bound by

  the instance declaration at Main.hs:70:14

In the expression: side * side

In the definition of `area':

area (SquareConstructor side) = side * side

 

I'm becoming lost in errors I don't comprehend

 

What bamboozles me is it seemed such a minor enhancement.



From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf
Of David Menendez
Sent: 21 December 2007 17:05
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling

 

On Dec 21, 2007 11:50 AM, Nicholls, Mark [EMAIL PROTECTED]
wrote:

Now I have

module Main where

data SquareType numberType = Num numberType = SquareConstructor
numberType


This is a valid declaration, but I don't think it does what you want it
to. The constraint on numberType applies only to the data constructor. 

That is, given an unknown value of type SquareType a for some a, we do
not have enough information to infer Num a.

For your code, you want something like:

instance (Num a) = ShapeInterface (SquareType a) where 
area (SquareConstructor side) = side * side


-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/  

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


[Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
I'm trying to teach myself HaskellI've spent a few hours going
through a few tutorialsand I sort of get the basics...

 

My interest in Haskell is specifically around the strength of the type
system.

 

After many years of OOP though my brain is wired up to construct
software in that 'pattern'a problem for me at the moment is I cannot
see how to construct programs in an OO style in HaskellI know this
is probably not the way to approach it...but I feel I need to master the
syntax before the paradigm.

 

I'm not fussed about mutability, and I'm not fussed about implementation
inheritance (as apposed to subtyping) my concerns are encapsulation
of 'state' and abstraction, and extension/expansiona simple example
would be.

 

interface IShape

{

Int GetArea();

}

 

 

class Square : IShape

{

Readonly int length;

 

Public Square(int length) { this.length  = length; }

 

Int GetArea() { return length * length;}

} 

 

Class Rectangle : IShape

{

Readonly int lengthA;

Readonly int lengthB;

 

Public Rectangle (int lengthA,int lengthB) { this.lengthA = lengthA;
this.lengthB = lengthB; }

 

Int GetArea() { return lengthA * lengthB;}

}

 

Class Circle : IShape

{

Readonly int radius;

 

Public Circle(int radius) { this.radius = radius; }

 

Int GetArea() { return pi * radius * radius;}

}

 

 

Client code.

 

Void Foo(IShape shape)

{

// look!I know nothing except its of type IShape.

 Int area = shape.GetArea();

}   

 

I can obviously at a later date add a new class Triangle, and not have
to touch any of the above code 

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


RE: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
OK I'll have to digest this and mess about a bitbut can I make an
observation at this point

If I define Shape like

data Shape = Circle Int
 | Rectangle Int Int
 | Square Int 

Isn't this now closed...i.e. the statement is effectively defining
that shape is this and only ever thisi.e. can I in another module
add new types of Shape? (sorry about all the quotation marks, but it's
a minefield of potential confusions over types, classes etc).

My other observation is...are the things on the right hand side of the
the ='s sign not types?

The lower version makes more sense to me...I'll have to give it a go

A P.S. would be...I tend to write code rather than mess about in the
GHCi shell.is there a way in code to output the type of a
value..i.e. the :t operation? 

-Original Message-
From: Thomas Davie [mailto:[EMAIL PROTECTED] 
Sent: 17 December 2007 11:04
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.


On 17 Dec 2007, at 10:46, Nicholls, Mark wrote:

 I can obviously at a later date add a new class Triangle, and not  
 have to touch any of the above code

Yes, and you can indeed do a similar thing in Haskell.  The natural  
thing to do here would be to define a type Shape...

data Shape = Circle Int
 | Rectangle Int Int
 | Square Int

area :: Shape - Int -- Note, this is an interesting type if you want  
the area of circles
area (Circle r) = pi * r^2
area (Rectangle h w) = h * w
area (Square l) = area (Rectangle l l)

If however, you *really* want to keep your shapes as being seperate  
types, then you'll want to invoke the class system (note, not the same  
as OO classes).

class Shape a where
   area :: a - Int

newtype Circle = C Int

instance Shape Circle where
   area (C r) = pi * r^2

newtype Rectangle = R Int Int

instance Shape Rectangle where
   area (R h w) = h * w

newtype Square = Sq Int

instance Shape Square where
   area (Sq l) = l * l

-- Now we can do something with our shapes
doubleArea :: Shape a = a - Int
doubleArea s = (area s) * 2

Hope that helps

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


RE: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
Ooo

The constructor of a newtype must have exactly one field   but `R' has
two In the newtype declaration for `Rectangle'

It doesn't like 

newtype Rectangle = R Int Int

-Original Message-
From: Thomas Davie [mailto:[EMAIL PROTECTED] 
Sent: 17 December 2007 11:04
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.


On 17 Dec 2007, at 10:46, Nicholls, Mark wrote:

 I can obviously at a later date add a new class Triangle, and not  
 have to touch any of the above code

Yes, and you can indeed do a similar thing in Haskell.  The natural  
thing to do here would be to define a type Shape...

data Shape = Circle Int
 | Rectangle Int Int
 | Square Int

area :: Shape - Int -- Note, this is an interesting type if you want  
the area of circles
area (Circle r) = pi * r^2
area (Rectangle h w) = h * w
area (Square l) = area (Rectangle l l)

If however, you *really* want to keep your shapes as being seperate  
types, then you'll want to invoke the class system (note, not the same  
as OO classes).

class Shape a where
   area :: a - Int

newtype Circle = C Int

instance Shape Circle where
   area (C r) = pi * r^2

newtype Rectangle = R Int Int

instance Shape Rectangle where
   area (R h w) = h * w

newtype Square = Sq Int

instance Shape Square where
   area (Sq l) = l * l

-- Now we can do something with our shapes
doubleArea :: Shape a = a - Int
doubleArea s = (area s) * 2

Hope that helps

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


RE: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
Ok...

Thanks I need to revisit data and newtype to work out what the
difference is I think.

-Original Message-
From: Jed Brown [mailto:[EMAIL PROTECTED] On Behalf Of Jed Brown
Sent: 17 December 2007 12:04
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.

On 17 Dec 2007, [EMAIL PROTECTED] wrote:

 Ooo

 The constructor of a newtype must have exactly one field but `R' has
 two In the newtype declaration for `Rectangle'

 It doesn't like 

 newtype Rectangle = R Int Int

You want

  data Rectangle = R Int Int

A newtype declaration will be completely erased at compile time.  That
is, when you have a declaration like

  newtype Circle = C Int

the compiled code will not be able to distinguish between a Circle and
an Int.  You do, however, get all the benefits of a separate entity in
the type system.  When your type only has one constructor, newtype is
preferred over data, but they are semantically equivalent.  There are
extensions which provide impressive newtype-deriving-foo (getting the
compiler to write fairly non-trivial instance declarations for you).

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


RE: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
No that's fineits all as clear as mud!..but that's not your
fault. 

To recap...

type introduces a synonym for another type, no new type is
createdit's for readabilities sake.

Newtype introduces an isomorphic copy of an existing type...but
doesn't copy it's type class membership...the types are
disjoint/distinct but isomorphic (thus only 1 constructor param).

data introduces a new type, and defines a composition of existing
types to create a new one based on - and (.

class introduces a constraint that any types declaring themselves to
be a member of this class...that functions must exist to satisfy the
constraint.

I'm sure that's wrong, but it's a good as I've got at the moment.

And to a degree it's all upside downwhat Haskell thinks are
types...I think are singnatures and what Haskell thinks is a type
class I think of as a type.it's not going to be easy.


-Original Message-
From: Thomas Davie [mailto:[EMAIL PROTECTED] 
Sent: 17 December 2007 12:35
To: Nicholls, Mark
Cc: Haskell Cafe
Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.


On 17 Dec 2007, at 12:22, Nicholls, Mark wrote:

 Ok...

 Thanks I need to revisit data and newtype to work out what the
 difference is I think.

Beware in doing so -- type, and newtype are not the same either.  type  
creates a type synonim.  That is, if I were to declare

type Jam = Int

then Jam and Int from that point on become completely interchangable,  
the only thing this does is make things readable.  For example, a  
parser might be described as a function that takes a list of tokens,  
and outputs a parse tree, and a list of unparsed tokens:

type Parser = [Token] - (ParseTree, [Token])

if I write some parser combinators, I can now give them clear types like

| :: Parser - Parser - Parser

I could however still write this, and it would have *exactly* the same  
meaning.

| :: ([Token] - (ParseTree, [Token])) - ([Token] - (ParseTree,  
[Token])) - [Token] - (ParseTree, [Token])

newtype on the other hand introduces a new type to the type system.   
Because of this, the type system has to be able to tell when you're  
using your new type, so a tag gets attached.

newtype Ham = Ham Int

This creates a type that contains only an integer, but is different  
from Int (and Jam) in the type system's eyes.  Thus, I cannot for  
example write

(Ham 5) + (Ham 6)

Because Ham is not Int and thus (+) does not work (or actually, more  
specifically, Ham is not a member of the class Num, the numeric types,  
and therefore (+) doesn't work).  This can of course be fixed thus:

newtype Ham = Ham Int deriving Num

Hope that helps

Tom Davie

p.s. Sorry for the slip with the newtype Rectangle.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
Not really with this...

The open case (as in OO) seems to be more like the Haskell class
construct, i.e. if new types declare themselves to be members of a class
then they must satisfy certain constaintsI can then specify equals
with the class and leave the onus on the implementor to implement
itthe data construct seems more analogous to a OO class
definition...which is closed in the same way. 
 
The approach is deliberate...but I accept may be harder than it needs to
be...I'm interested in Haskell because of the alleged power/formality of
it's type system against the relatively weakness of OO ones...the irony
at the moment is that they do not really seem to correspond
directlyand OO type system seems to (loosely) correlate to Haskell
type class system, and an OO class system (loosely) to Haskels type
system, though in OOP's they are unpleasantly tangled.



-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of apfelmus
Sent: 17 December 2007 12:34
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: OOP'er with (hopefully) trivial
questions.

Nicholls, Mark wrote:
 
 data Shape = Circle Int
  | Rectangle Int Int
  | Square Int 
 
 Isn't this now closed...i.e. the statement is effectively defining
 that shape is this and only ever thisi.e. can I in another module
 add new types of Shape?

Yes, but in most cases, this is actually a good thing. For instance, you

can now define equality of two shapes:

   equal :: Shape - Shape - Bool
   equal (Circle x)(Circle y)= x == y
   equal (Rectangle x1 x2) (Rectangle y1 y2) = x1 == x2  y1 == y2
   equal (Square x)(Square y)= x == y

In general, the open approach is limited to functions of the form

   Shape - ... - Shape / Int / something else

with no Shape occurring in the other ... arguments.

 I'm trying to teach myself HaskellI've spent a few hours going
 through a few tutorialsand I sort of get the basics...
 [...]
 After many years of OOP though my brain is wired up to construct
 software in that 'pattern'a problem for me at the moment is I
cannot
 see how to construct programs in an OO style in HaskellI know this
 is probably not the way to approach it...but I feel I need to master
the
 syntax before the paradigm.

This approach is probably harder than it could be, you'll have a much 
easier time learning it from a paper-textbook like

   http://www.cs.nott.ac.uk/~gmh/book.html
   http://web.comlab.ox.ac.uk/oucl/publications/books/functional/
   http://haskell.org/soe/

After all, it's like learning programming anew.


Regards,
apfelmus

___
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] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
Ahhh

I'll give it a read.

thanks

-Original Message-
From: Henning Thielemann [mailto:[EMAIL PROTECTED] 
Sent: 17 December 2007 13:05
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.


On Mon, 17 Dec 2007, Nicholls, Mark wrote:

 After many years of OOP though my brain is wired up to construct
 software in that 'pattern'a problem for me at the moment is I
cannot
 see how to construct programs in an OO style in HaskellI know this
 is probably not the way to approach it...but I feel I need to master
the
 syntax before the paradigm.

This issue is rather a FAQ. Let's look what our Wiki provides:
  http://www.haskell.org/haskellwiki/OOP_vs_type_classes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
No neither do II think we can drop that bitI think I got
confused about it for a second.not unsurprisingly.

 



From: Brent Yorgey [mailto:[EMAIL PROTECTED] 
Sent: 17 December 2007 15:38
To: Nicholls, Mark
Cc: Thomas Davie; Haskell Cafe
Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.

 

 

On Dec 17, 2007 8:04 AM, Nicholls, Mark [EMAIL PROTECTED] wrote:

No that's fineits all as clear as mud!..but that's not your
fault.

To recap...

type introduces a synonym for another type, no new type is
createdit's for readabilities sake. 

Newtype introduces an isomorphic copy of an existing type...but
doesn't copy it's type class membership...the types are
disjoint/distinct but isomorphic (thus only 1 constructor param).

data introduces a new type, and defines a composition of existing
types to create a new one based on - and (.

class introduces a constraint that any types declaring themselves to 
be a member of this class...that functions must exist to satisfy the
constraint.

I'm sure that's wrong, but it's a good as I've got at the moment.

And to a degree it's all upside downwhat Haskell thinks are 
types...I think are singnatures and what Haskell thinks is a type
class I think of as a type.it's not going to be easy.

 


I think you've got it pretty well!   The one quibble I would have with
your recap is that I'm not sure what you mean by saying that data
creates a new type 'based on - and ('.  Other than that it seems
pretty spot-on. =) 

-Brent

 

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


RE: Re[2]: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Nicholls, Mark
My Haskell is not up to understanding themI'm still writing hello
world programswhat I read, gave me a good initial hint as to whats
going on...I just need to get my Haskell going before I can jump in the
deep end.
 
-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 17 December 2007 16:37
To: Nicholls, Mark
Cc: Henning Thielemann; haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] OOP'er with (hopefully) trivial
questions.

Hello Mark,

Monday, December 17, 2007, 4:47:50 PM, you wrote:

 I'll give it a read.
   http://www.haskell.org/haskellwiki/OOP_vs_type_classes

i recommend you to read two papers mentioned in References section
there. at least i'm one of this page authors and i don't think that i
had very good understanding of type classes on the moment when this
page was written. OTOH it also contains section written by John
Meacham - it should be better because John is author of one Haskell
compiler


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