OOP'er with (hopefully) trivial questions.....

I'm trying to teach myself Haskell....I've spent a few hours going through a few tutorials....and 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 Haskell....I 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/expansion....a 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....

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

OK I'll have to digest this and mess about a bit....but 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 this....i.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:tom.davie@gmail.com] 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

On 17 Dec 2007, at 11:14, Nicholls, Mark wrote:
OK I'll have to digest this and mess about a bit....but 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 this....i.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).
That's correct, another module could not add constructors to this type. The idea here is that you tell it all of the possible ways to construct Shape, and can then write functions to deal with it elsewhere.
My other observation is...are the things on the right hand side of the the "="'s sign not types? Correct, they're constructors. So you could never for example write a function that accepts only Rectangles (unless you start getting into odd type extensions)
The lower version makes more sense to me...I'll have to give it a go....
Both versions make sense. They differ only in how "heavy weight" they are. Defining a type allows you to do pattern matching on the constructors, and is a much better way of defining anything you know the structure of in the first place. Using the class system on the other hand, gives you more flexibility, but at the cost of a lot of readability. The class system is designed to be able to describe things that aren't explicitly the same type, but exhibit similar properties. For example the Eq class describes all things that are equatable, it defines the (==) and (/=) operators. Your Shape class describes all types in which it's sane to compute an area.
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?
Take a look at the Typable class. Although, pretty much any code that you can compile can be loaded into ghci without modification, and that's by far the easier way of finding the types of things. Bob

Thomas Davie wrote:
Take a look at the Typable class. Although, pretty much any code that you can compile can be loaded into ghci without modification, and that's by far the easier way of finding the types of things.
Is there a way to make ghci to know also the symbols which are not exported? My problem is that :t <unexportedSymbolName> reports undefined. Is there a way to make :t working without first exporting <unexportedSymbolName> and then reloading the module in ghci and asking with :t again? Peter.

There was a thread about this recently.
In any case, if you load the code interpreted (which happens if there
is no .o or .hi file of the module lying around), then you can
look inside all you want. But if it loads compiled, then you only
have access to the exported symbols. The reason is because of
inlining optimizations; you know about the encapsulation of the module
when you compile it, and you can optimize the memory and
code usage based on compiling functions that are not exported
differently. That's my weak understanding, at least.
Luke
On Dec 17, 2007 5:52 PM, Peter Hercek
Thomas Davie wrote:
Take a look at the Typable class. Although, pretty much any code that you can compile can be loaded into ghci without modification, and that's by far the easier way of finding the types of things.
Is there a way to make ghci to know also the symbols which are not exported? My problem is that :t <unexportedSymbolName> reports undefined. Is there a way to make :t working without first exporting <unexportedSymbolName> and then reloading the module in ghci and asking with :t again?
Peter.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Luke Palmer wrote:
There was a thread about this recently.
In any case, if you load the code interpreted (which happens if there is no .o or .hi file of the module lying around), then you can look inside all you want. But if it loads compiled, then you only have access to the exported symbols. The reason is because of inlining optimizations; you know about the encapsulation of the module when you compile it, and you can optimize the memory and code usage based on compiling functions that are not exported differently. That's my weak understanding, at least.
Luke
Great. Cleaning before loading into ghci works. Thanks, Peter.

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 this....i.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 Haskell....I've spent a few hours going through a few tutorials....and 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 Haskell....I 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

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 constaints....I can then specify "equals" with the class and leave the onus on the implementor to implement it....the 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 directly....and 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: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] 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 this....i.e. can I in another module add new "types" of Shape?
I'm trying to teach myself Haskell....I've spent a few hours going through a few tutorials....and 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 Haskell....I know this is probably not the way to approach it...but I feel I need to master
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. 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

From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Nicholls, Mark
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 constaints....I can then specify "equals" with the class and leave the onus on the implementor to implement it....the data construct seems more analogous to a OO class definition...which is closed in the same way.
This may or may not help, but anyway... As Henning has pointed out, this is a FAQ. However, his recommended page (OOP_vs_type_classes) is quite involved. As a counterpoint, I really liked Lennart's example and summary from a couple of years ago: http://www.haskell.org/pipermail/haskell/2005-June/016058.html (I've added it to section 5 of this page: http://www.haskell.org/haskellwiki/Existential_type) The key point (IMO): "with the object oriented way it's easier to add a new kind of shape and with the functional way it's easier to add a new operation." Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

On Dec 17, 2007 1:18 PM, 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 constaints....I can then specify "equals" with the class and leave the onus on the implementor to implement it....the data construct seems more analogous to a OO class definition...which is closed in the same way.
Yes that's pretty much true. In lots of cases you do have tons of different representations of a specific type that is known at to be closed. E.g. singly linked list has two cases it's either a "Link" or it's the end of the list: data List a = Link a (List a) | Nil You could do this in C++ with two different classes inheriting from a common base class, and then use RTTI to discover what variant of "List" something is, or add a virtual function called "isLink" or something, or maybe just have a single variant but add a boolean or an enum field describing wether or not the "Link" pointer is valid. As you see it gets messy (and in this trivial case you would use the "built in" two-way case of pointers, where you can specify "Nil" as simply a link with a null "tail" - but that's not always the possible, and even in this case I find it much nicer to explicitly use two completely different representations for the two variants). In general you don't tend to use this sort of tagged union to build stuff in OOP so there's no direct correspondence to "typical" OOP patterns. So one side effect of learning Haskell is (or at least was to me) a greater familiarity with that approach to describing data, which is simple and powerful enough that you sometimes emulate it even when it gets a bit messy in other languages. It really gets nice when you start defining functions on the data type using pattern matching, as everything is just extremely clear and nice since you only deal with one case at a time.. Here's a few examples using the list (uncompiled): isEmpty Nil = True isEmpty _ = False length Nil = 0 length (Link _ xs) = 1 + length xs concat Nil xs = xs concat (Link x xs) ys = Link x (concat xs ys) -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

On Dec 17, 2007 8:18 AM, Nicholls, Mark
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 directly....and 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.
When I was learning Haskell, I found it helpful to think this way: In an OO
system, classes describe objects. In Haskell, classes decribe types.
It may also be helpful to note that Haskell's class system can be emulated
in the language itself[1] by a technique known as "dictionary passing".
For example, the Eq class is equivalent to a function of type a -> a ->
Bool, for some a.
type EqD a = a -> a -> Bool
So any time I have a function that uses Eq,
foo :: Eq a => a -> a -> a -> a
foo a b c = if a == b then c else b
I could define an equivalent function without it
fooBy :: EqD a -> a -> a -> a -> a
fooBy eq a b c = if eq a b then c else b
The difference between foo and fooBy is that fooBy requires me to explicitly
provide the Eq dictionary, whereas the compiler takes care of providing it
to foo.
A lot of functions in Data.List exist in "foo" and "fooBy" forms.
[1] This isn't entirely true if we're talking about Haskell 98. Some classes
dictionaries can't be defined without an extension, but that extension is
widely supported and will almost certainly be in the next language standard.
--
Dave Menendez

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:tom.davie@gmail.com] 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

On Dec 17, 2007 10:47 PM, Nicholls, Mark
"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"
A newtype can only have one constructor, with one argument, and is essentially a wrapper for that argument type. In the general case, you want to use "data" instead of "newtype": data Rectangle = R Int Int Stuart

A newtype can only have one constructor, with one argument, and is essentially a wrapper for that argument type.
In the general case, you want to use "data" instead of "newtype":
data Rectangle = R Int Int
I'm sure there's a trivial explanation for this, but here's something that I've always kind of wondered about: Given a single constructor type like "data X = X A B C" can't that be transformed into "newtype X = X (A, B, C)"? There must be some difference, because if there weren't we could transform all single constructor types that way, and dispense with newtype entirely.

I'm sure there's a trivial explanation for this, but here's something that I've always kind of wondered about: Given a single constructor type like "data X = X A B C" can't that be transformed into "newtype X = X (A, B, C)"? There must be some difference, because if there weren't we could transform all single constructor types that way, and dispense with newtype entirely.
Oops, nevermind, I just saw the other thread and link to http://www.haskell.org/haskellwiki/Newtype. Ok, so that seems like a pretty subtle diffenence... I'm assuming the rationale behind differentiating between a single constructor data and newtype is so that data types don't suddenly change their behaviour around undefined when they have only one constructor. I would find example y3 surprising if I came across it in real code!

On 12/17/07, Evan Laforge
Oops, nevermind, I just saw the other thread and link to http://www.haskell.org/haskellwiki/Newtype. Ok, so that seems like a pretty subtle diffenence... I'm assuming the rationale behind differentiating between a single constructor data and newtype is so that data types don't suddenly change their behaviour around undefined when they have only one constructor. I would find example y3 surprising if I came across it in real code!
It's not that subtle if you think about what newtype is for. Newtype is like "type", except that you're not just declaring a type synonym, but asking the typechecker to check that you don't use the synonym interchangeably with the type it's standing in for. Types declared with newtype and with type are supposed to act exactly the same way at runtime. In order to act exactly the same way at runtime, if you write newtype X = X A, X _|_ has to be indistinguishable from _|_ at runtime. In other words, the data constructor X has to be strict. In types declared with "data", constructors are lazy -- if they weren't, you wouldn't be programming in Haskell. Cheers, Tim -- Tim Chevalier * catamorphism.org * Often in error, never in doubt "People. Can't live with 'em, can't legally set fire to 'em." -- Sheree Schrager

On 12/17/07, Evan Laforge
I'm sure there's a trivial explanation for this, but here's something that I've always kind of wondered about: Given a single constructor type like "data X = X A B C" can't that be transformed into "newtype X = X (A, B, C)"? There must be some difference, because if there weren't we could transform all single constructor types that way, and dispense with newtype entirely.
Strictness. In newtype X = X A, the A field is strict. In data X = X A, the A field is lazy. So the compiler can't just turn all single-constructor "data" types into "newtypes". (To generalize, if you were going to allow newtypes like "newtype X = X (A, B, C)", the tuple would be unboxed, and you'd have the same strictness/laziness distinction.) This is explained in section 4.2.3 of the H98 Report: http://www.haskell.org/onlinereport/decls.html Cheers, Tim -- Tim Chevalier * catamorphism.org * Often in error, never in doubt "Do we learn from our mistakes? I surely hope not / Takes all the fun out of making them again."--Trout Fishing In America

Am Montag, 17. Dezember 2007 19:26 schrieb Tim Chevalier:
On 12/17/07, Evan Laforge
wrote: I'm sure there's a trivial explanation for this, but here's something that I've always kind of wondered about: Given a single constructor type like "data X = X A B C" can't that be transformed into "newtype X = X (A, B, C)"? There must be some difference, because if there weren't we could transform all single constructor types that way, and dispense with newtype entirely.
Strictness. In newtype X = X A, the A field is strict. In data X = X A, the A field is lazy. So the compiler can't just turn all single-constructor "data" types into "newtypes".
Evan talked about data constructors with multiple fields, not with one single field.
(To generalize, if you were going to allow newtypes like "newtype X = X (A, B, C)", the tuple would be unboxed, and you'd have the same strictness/laziness distinction.)
This is not a generalization of what you talked about. Why should the tuple type be unboxed? Tuple types are boxed, meaning there is a difference between _|_ and (_|_,…,_|_). If you write newtype X = X (A, B, C) then X doesn’t add another level of indirection but the level of indirection introduced by the tuple constructor remains, of course. So you could write the above newtype declaration instead of data X = X A B C. _|_ would then be represented as X _|_ (equal to _|_) and X _|_ _|_ _|_ as X (_|_,_|_,_|_). Instead of pattern matching against X a b c, you would have to pattern match against X (a,b,c). So why not use the above newtype declaration instead of multi-field data declarations? One strong reason is that tuple types are itself algebraic data types which could be defined by data declarations if they wouldn’t use special syntax. So we would have to represent a tuple type by a newtype whose field type would be the tuple type we just want to represent.
[…]
Cheers, Tim
Best wishes, Wolfgang

On 12/17/07, Wolfgang Jeltsch
This is not a generalization of what you talked about. Why should the tuple type be unboxed? Tuple types are boxed, meaning there is a difference between _|_ and (_|_,…,_|_). If you write
newtype X = X (A, B, C)
then X doesn't add another level of indirection but the level of indirection introduced by the tuple constructor remains, of course. So you could write the above newtype declaration instead of
data X = X A B C.
I interpreted Evan's question as "why can't you have newtypes with multiple fields?" -- i.e., newtype X = X A B C -- and that's the question I was answering. But maybe I misunderstood. Cheers, Tim -- Tim Chevalier * catamorphism.org * Often in error, never in doubt "After three days without programming, life becomes meaningless." -- James Geoffrey

I interpreted Evan's question as "why can't you have newtypes with multiple fields?" -- i.e., newtype X = X A B C -- and that's the question I was answering. But maybe I misunderstood.
Well, the question was both, and "strictness" answers both. Thanks for the clarification. I should have realized that of course (,) is an ADT just like all the rest. I guess that means that 'data X = X Y Z' is always preferable to 'newtype X = X (Y, Z)' since the latter is just like the former but with some extra typing.

On 17 Dec 2007, Nicholls.Mark@mtvne.com 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

Ok... Thanks I need to revisit data and newtype to work out what the difference is I think. -----Original Message----- From: Jed Brown [mailto:five9a2@gmail.com] 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, Nicholls.Mark@mtvne.com 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

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.

No that's fine....its all as clear as mud!......but that's not your fault. To recap... "type" introduces a synonym for another type, no new type is created....it'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 down....what 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:tom.davie@gmail.com] 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.

From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Nicholls, Mark
To recap...
"type" introduces a synonym for another type, no new type is created....it'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.
As an aside, I was wondering exactly what the differences are between newtype and data i.e. between
newtype A a = A a
and
data A a = A a
According to: http://www.haskell.org/onlinereport/decls.html#sect4.2.3 newtype is, umm, stricter than data i.e. newtype A undefined = undefined, but data A undefined = A undefined. Other than that, newtype just seems to be an optimization hint. Is that a more-or-less correct interpretation? Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

From: Bayley, Alistair
newtype A a = A a and data A a = A a
Sorry, that should read:
newtype A = A a data A = A a
Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

From: Bayley, Alistair
Sorry, that should read:
newtype A = A a data A = A a
Ignore that; I was right first time. Sorry 'bout the spam, and the lack of brain. ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

On Dec 17, 2007 8:51 AM, Bayley, Alistair < Alistair_Bayley@invescoperpetual.co.uk> wrote:
As an aside, I was wondering exactly what the differences are between newtype and data i.e. between
newtype A a = A a
and
data A a = A a
According to: http://www.haskell.org/onlinereport/decls.html#sect4.2.3 newtype is, umm, stricter than data i.e. newtype A undefined = undefined, but data A undefined = A undefined. Other than that, newtype just seems to be an optimization hint. Is that a more-or-less correct interpretation?
Pretty much. Newtype is nice to have, but I don't think there's any program
you can write that couldn't be rewritten to use data (with a possible loss
of efficiency).
The difference that surprised me is the difference between
newtype A a = A a
and
data A a = A !a
If we define a function like this,
seqA (A a) = ()
Under the first definition of A,
seqA undefined = ()
Under the second,
seqA undefined = undefined
The difference is that pattern-matching a newtype doesn't do any evaluation.
--
Dave Menendez

On 17 Dec 2007, at 7:39 AM, David Menendez wrote:
On Dec 17, 2007 8:51 AM, Bayley, Alistair
wrote: As an aside, I was wondering exactly what the differences are between newtype and data i.e. between newtype A a = A a
and
data A a = A a
According to: http://www.haskell.org/onlinereport/decls.html#sect4.2.3 newtype is, umm, stricter than data i.e. newtype A undefined = undefined, but data A undefined = A undefined. Other than that, newtype just seems to be an optimization hint. Is that a more-or-less correct interpretation?
Pretty much. Newtype is nice to have, but I don't think there's any program you can write that couldn't be rewritten to use data (with a possible loss of efficiency).
The difference that surprised me is the difference between
newtype A a = A a
and
data A a = A !a
If we define a function like this,
seqA (A a) = ()
Under the first definition of A,
seqA undefined = ()
Under the second,
seqA undefined = undefined
The difference is that pattern-matching a newtype doesn't do any evaluation.
So there is a program (or, rather, type) you can write with newtype that can't be written with data: newtype T = T T jcc

Jonathan Cast wrote:
So there is a program (or, rather, type) you can write with newtype that can't be written with data:
newtype T = T T
That compiles, and anything of type T is ⊥. But it breaks my mental model of what the compiler does for newtypes. I always think of them as differently typed versions that share the same underlying "data" declaration and representation; and then the compiler erases the type information. So let me think about this one. Looking at the Haskell 98 Report http://www.haskell.org/onlinereport/decls.html#sect4.2.3 "A declaration of the form newtype cx => T u1 ... uk = N t introduces a new type whose representation is the same as an existing type. The type (T u1 ... uk) renames the datatype t. It differs from a type synonym in that it creates a distinct type that must be explicitly coerced to or from the original type" What I don't see is anything that discusses what "newtype T = T T" could mean. Is there any difference in how GHC treats "newtype T = T T" versus "data T"? -- Chris

On Mon, 2007-12-17 at 13:51 +0000, Bayley, Alistair wrote:
From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Nicholls, Mark
To recap...
"type" introduces a synonym for another type, no new type is created....it'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.
As an aside, I was wondering exactly what the differences are between newtype and data i.e. between
newtype A a = A a
and
data A a = A a
According to: http://www.haskell.org/onlinereport/decls.html#sect4.2.3 newtype is, umm, stricter than data i.e. newtype A undefined = undefined, but data A undefined = A undefined. Other than that, newtype just seems to be an optimization hint. Is that a more-or-less correct interpretation?
More less than more. There is a context that can distinguish a newtype from a data type. This is explained on this wiki page that addresses exactly this question. http://www.haskell.org/haskellwiki/Newtype

On Dec 17, 2007 8:04 AM, Nicholls, Mark
No that's fine....its all as clear as mud!......but that's not your fault.
To recap...
"type" introduces a synonym for another type, no new type is created....it'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 down....what 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

No neither do I....I think we can drop that bit....I think I got
confused about it for a second.....not unsurprisingly.
________________________________
From: Brent Yorgey [mailto:byorgey@gmail.com]
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

Am Montag, 17. Dezember 2007 13:04 schrieb Jed Brown:
[…]
When your type only has one constructor, newtype is preferred over data, but they are semantically equivalent.
They are *not* semantically equivalent, as has already been said more or less. data adds an extra level of indirection. With data A a = MkA a, _|_ (i.e., undefinedness) is different from MkA _|_. If I don’t know anything about a value of A a then this is not the same as knowing that the value is at least an application of MkA. newtype just creates wrapper types and it’s very unfortunate that it uses syntax similar to data because it’s very different. With newtype A a = MkA a, you just create a wrapper type A a for each type a. Applying the constructor just means casting from a to A a, and pattern matching just means casting from A a to a. Type-casting _|_ yields botton, that’s why MkA _|_ is _|_ and pattern matching _|_ against A x doesn’t fail but assigns _|_ to x.
[…]
Best wishes, Wolfgang

Very interesting, I did not know that! I thought newtype was an optimization of data, and that "newtype" was bad terminology. But if newtype is just a wrapper around a type, then the name is choosen well. I'm a bit confused why then one needs a data-constructor-like tag to construct a newtype value then? Is this to avoid having to add a type signature (for type inference)? I find this a bit weird since newtype Foo = Foo Int bar = Foo 123 does not safe a lot of keystrokes ;) compared to -- Incorrect Haskell follows newtype Foo = Int bar = 123::Foo -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Wolfgang Jeltsch Sent: Monday, December 17, 2007 5:39 PM To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions..... Am Montag, 17. Dezember 2007 13:04 schrieb Jed Brown:
[…]
When your type only has one constructor, newtype is preferred over data, but they are semantically equivalent.
They are *not* semantically equivalent, as has already been said more or less. data adds an extra level of indirection. With data A a = MkA a, _|_ (i.e., undefinedness) is different from MkA _|_. If I don’t know anything about a value of A a then this is not the same as knowing that the value is at least an application of MkA. newtype just creates wrapper types and it’s very unfortunate that it uses syntax similar to data because it’s very different. With newtype A a = MkA a, you just create a wrapper type A a for each type a. Applying the constructor just means casting from a to A a, and pattern matching just means casting from A a to a. Type-casting _|_ yields botton, that’s why MkA _|_ is _|_ and pattern matching _|_ against A x doesn’t fail but assigns _|_ to x.
[…]
Best wishes, Wolfgang _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Peter Verswyvelen wrote:
Very interesting, I did not know that!
I thought newtype was an optimization of data, and that "newtype" was bad terminology. But if newtype is just a wrapper around a type, then the name is choosen well.
I'm a bit confused why then one needs a data-constructor-like tag to construct a newtype value then? Is this to avoid having to add a type signature (for type inference)? I find this a bit weird since
newtype Foo = Foo Int bar = Foo 123
does not safe a lot of keystrokes ;) compared to
-- Incorrect Haskell follows newtype Foo = Int bar = 123::Foo
You've broken the principle type property. let's stay away from numeric literals (which are fiddly because they're overloaded already in typeclass Num) and take a concrete type: data Foo = A | B newtype Bar = Bar Foo Now, the type of "A" is "Foo". If I was allowed to write "A::Bar" then I no longer have a simple principle type for "A": it appears that the type of "A" is "Foo" or "Bar" depending how I annotate it. Of course, I can make this work fine, using some form of constraint. Haskell already has constraints, we call them classes, and I could imagine giving "A" the principle type "(FooOrNewtypeOfFoo a) => a" However, that's a bunch of added complexity for such a simple feature :) Much nicer just to write "A" :: Foo and "Bar A" :: Bar. Jules

Thomas Davie
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
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
There's a third way, too, and I haven't seen anybody mention it yet (apologies if I just missed it). You can provide an explicit record of the relevant "member functions", and "instantiate" it in different ways. E.g. data Shape = Shape { area :: Int } square x = Shape (x^2) rectangle x y = Shape (x*y) circle r = Shape (pi*r^2) -k -- If I haven't seen further, it is by standing in the footprints of giants

There's a third way, too, and I haven't seen anybody mention it yet
I've noticed it, but there are some problems with this representation, so I decided not to mention it. It's OK as far as we don't want functions working on two areas - I don't see, how we can implement, say, intersect :: Shape -> Shape -> Bool in this way. However, it's a useful pattern.
(apologies if I just missed it). You can provide an explicit record of the relevant "member functions", and "instantiate" it in different ways. E.g.
data Shape = Shape { area :: Int }
square x = Shape (x^2) rectangle x y = Shape (x*y) circle r = Shape (pi*r^2)

On Mon, 2007-12-17 at 22:12 +0300, Miguel Mitrofanov wrote:
There's a third way, too, and I haven't seen anybody mention it yet
I've noticed it, but there are some problems with this representation, so I decided not to mention it. It's OK as far as we don't want functions working on two areas - I don't see, how we can implement, say, intersect :: Shape -> Shape -> Bool in this way. However, it's a useful pattern.
And how do you do it in a "typical" OO language like Java or C# or Smalltalk?

Miguel Mitrofanov
I've noticed it, but there are some problems with this representation, so I decided not to mention it. It's OK as far as we don't want functions working on two areas - I don't see, how we can implement, say, intersect :: Shape -> Shape -> Bool in this way. However, it's a useful pattern.
Yes, there are different trade offs, it depends what you want to do. The AlgDT makes intersect simple: intersect :: Shape -> Shape -> Bool intersect (Circle x) (Circle y) = ... intersect (Circle x) (Rectangle x y) = ... : As Derek hints at, this isn't so nice in C++ and friends, you probably will end up with // Apologies for any mistakes in the code, it's been a while. class Circle : public Shape { : bool intersect(s){ if(dynamic_cast<Circle>(s)){...} else if (dynamic_cast<Rectangle>(s)){...} : } } etc. In addition to being very verbose and tedious code to write, you will have no idea if you have managed to cover all cases. Your 'intersect' function is spread all over the place. -k -- If I haven't seen further, it is by standing in the footprints of giants

Miguel Mitrofanov wrote:
There's a third way, too, and I haven't seen anybody mention it yet
I've noticed it, but there are some problems with this representation, so I decided not to mention it. It's OK as far as we don't want functions working on two areas - I don't see, how we can implement, say, intersect :: Shape -> Shape -> Bool in this way. However, it's a useful pattern.
The problem is no better or worse for this third way than for type classes. class Shape a where { intersect :: Shape b => a -> b -> Bool } data Shape a = { intersect :: Shape b => a -> b -> Bool } in fact, the syntax is rather similar, too! :) Jules

On Dec 18, 2007 7:51 AM, Jules Bean
class Shape a where { intersect :: Shape b => a -> b -> Bool }
Shouldn't this be class Shape a where ....whatever.... class (Shape a, Shape b) => Intersectable a b where intersect :: a -> b -> Bool With your definition I don't see how you could make it work, as you would have to write a function that takes care of this shape intersecting with any other shape, but this is exactly the problem the classes should solve! Cheers, -- Felipe.

Felipe Lessa wrote:
On Dec 18, 2007 7:51 AM, Jules Bean
wrote: class Shape a where { intersect :: Shape b => a -> b -> Bool }
Shouldn't this be
class Shape a where ....whatever....
class (Shape a, Shape b) => Intersectable a b where intersect :: a -> b -> Bool
With your definition I don't see how you could make it work, as you would have to write a function that takes care of this shape intersecting with any other shape, but this is exactly the problem the classes should solve!
Yes, that's a better solution, certainly. MPTCs are not haskell though :P I'm half joking, but there are solutions which don't involve non-standard extensions even ones as popular as MPTCs. I didn't really think mine was particularly useful, just pointing out the design space, and in particular the precise parallel between the classes approach and the explicit dictionary approach. Jules

Felipe Lessa wrote:
class Shape a where ....whatever....
class (Shape a, Shape b) => Intersectable a b where intersect :: a -> b -> Bool
This looks nice at first sight, but is it usefull in practice? I can somehow express the type "any shape wich is intersectable with a given other shape", but it is a pain: data Intersectable a = forall b . Intersectable a b => Intersectable b instance Intersectable a (Intersectable b) where intersect a (Intersectable b) = intersect a b Now consider I write another binary function as a type class: class (Shape a, Shape b) => Containment a b where contains :: a -> b -> Bool data Containment a = forall b . Containment a b => Containment b instance Containment a (Containment b) where contains a (Containment b) = contains a b I cannot combine these types to express "any shape wich is intersectable and can be united with a given other shape" without writing another existiential wrapper. I cannot express "a list of pairwise intersectable shapes" either. Things get even worse if we consider a different definition of intersect: class (Shape a, Shape b, Shape c) => Intersect a b c | a b -> c where intersect :: a -> b -> c My conclusion: To make Haskell a better OO language then current OO languages, we need either first-class typeclasses (to quantify over the classes an existential wrapped value supports) or inference of existential wrappers (to infer complicated wrappers automatically). (Since it's not the goal of Haskell to be any OO language at all this may not be a problem) Tillmann

Don't think the "Haskell's Overlooked Object System" paper has been posted
to this thread yet:
http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf
--s
On 12/18/07, Lutz Donnerhacke
* Tillmann Rendel wrote:
My conclusion: To make Haskell a better OO language
Haskell is not an OO language and never should be.
(Since it's not the goal of Haskell to be any OO language at all this may not be a problem)
Ack. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
Perhaps introduce an existensial quantification? data Shape = forall a. Sh a => Shape a class Sh a where area :: a -> Float data Circle = Circle Float instance Sh Circle area (Circle r) = pi*r*2 data Rect = Rect Float Float instance Sh Rect area (Rect h w) = h * w doubleArea :: Shape -> Float doubleArea (Shape x) = (area x) * 2 I think this is more in the traditional OOP sense. But this way or Tom's: one would have to convert functions like equality over Values of type Shape into equality over different types (Circle and Rect). This can be done using case analysis over the types with something like read. Kind regards, Chris.

"Nicholls, Mark"
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 Haskell?.I know this is probably not the way to approach it?but I feel I need to master the syntax before the paradigm.
Mostly, you'd use an algebraic data type. I.e. data Shape = Square Int | Rectangle Int Int | Circle Int area :: Shape -> Int area (Square x) = x^2 area (Rectangle x y) = x * y area (Circle r) = pi*r^2 -k -- If I haven't seen further, it is by standing in the footprints of giants

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 Haskell....I 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

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 Haskell....I know this is probably not the way to approach it...but I feel I need to master
Ahhh I'll give it a read. thanks -----Original Message----- From: Henning Thielemann [mailto:lemming@henning-thielemann.de] 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: 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

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, Bulat mailto:Bulat.Ziganshin@gmail.com

My Haskell is not up to understanding them....I'm still writing hello world programs....what 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:bulat.ziganshin@gmail.com] 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, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (28)
-
apfelmus
-
Bayley, Alistair
-
Brent Yorgey
-
Bulat Ziganshin
-
C.M.Brown
-
ChrisK
-
David Menendez
-
Derek Elkins
-
Evan Laforge
-
Felipe Lessa
-
Henning Thielemann
-
Jed Brown
-
Jonathan Cast
-
Jules Bean
-
Ketil Malde
-
Luke Palmer
-
Lutz Donnerhacke
-
Miguel Mitrofanov
-
Nicholls, Mark
-
Peter Hercek
-
Peter Verswyvelen
-
Sebastian Sylvan
-
Sterling Clover
-
Stuart Cook
-
Thomas Davie
-
Tillmann Rendel
-
Tim Chevalier
-
Wolfgang Jeltsch