
OK, recently I posed a question about rethinking some OO idioms, and that spawned some useful discussion. I now have a followup question. One of the best features of OO programming is that of inheritance. It can be used to slightly alter the behavior of objects without requiring modification to existing code or breaking compatibility with existing APIs. As an example, say I have a ConfigParser class. This class can read in configuration files, provides various get/set methods to access them, and can write them back out. Now say I would like to make this a little more powerful. Maybe I want to support the use of environment variables in my config file, so if there's a reference to $FOO in the file, it will be replaced by the contents of $FOO in the environment. In OO, I would make a new EnvConfigParser class. I'd override the read() method. My new read() would probably start by calling the parent's read() method, to get parsing for free. Then it could iterate over the data, doing its environment variable substitution. Now, in Haskell, we obviously have no objects like this. We do have something that provides some of the same benefits -- typeclasses. However, from what I can determine, they don't support algorithm inheritance like objects do in an OOP. Specifically, it seems impossible to have two instances of a single typeclass that work on the same type, while having one share most of the code with the other. I'm wondering if there is a Haskell design pattern that I'm missing that would provid ethe kind of benefits that one gets from inheritance in the OO world. -- John -- John Goerzen Author, Foundations of Python Network Programming http://www.amazon.com/exec/obidos/tg/detail/-/1590593715

On Tue, 12 Oct 2004, John Goerzen wrote:
One of the best features of OO programming is that of inheritance. It can be used to slightly alter the behavior of objects without requiring modification to existing code or breaking compatibility with existing APIs.
I hesitate to express a contrary opinion since it'll sound as though I'm defending Haskell's limitations, but that's actually not the case here -- this was true even before I learned Haskell. In my own OOP code (mainly C++) I've rarely used implementation inheritance, and when I have I've never felt entirely happy about the way it turned out; it always seemed a bit fragile and hacky. When I want to take advantage of polymorphism I usually use abstract interfaces, and when I want to share code I usually use containment and delegation, which has always struck me as more robust. In any case, Haskell does support polymorphic abstract interfaces and containment and delegation. In your ConfigParser example you would have an interface (say IConfigParser) which would be represented as a type class, and two implementations (ConfigParser and EnvConfigParser) which would be represented as instances of the type class. E.g. class IConfigParser a where newConfigParser :: IO a readConfigFile :: a -> FilePath -> IO () getFoo :: a -> IO Foo setFoo :: a -> Foo -> IO () ... data ConfigParser = ... instance IConfigParser ConfigParser where ... data EnvConfigParser = ECP ConfigParser instance IConfigParser EnvConfigParser where newConfigParser = liftM ECP newConfigParser readConfigFile (ECP cp) path = readConfigFile cp path >> envSubst cp getFoo (ECP cp) = getFoo cp ... I should say, though, that this is very unidiomatic code. Partly this is because I don't quite understand the meaning of your ConfigParser class -- does it exist before a configuration file is read? What is the meaning of having more than one instance? Parsing configuration files strikes me as more verb than noun, and I'd be more inclined in this case to declare a single ConfigData type, a single function to write it to a file, and two functions to read it, one with environment substitution and one without. So I suppose my advice is twofold: 1. Try replacing implementation inheritance with containment and delegation when you translate to Haskell. 2. Try revisiting the original problem and thinking about how to solve it in a Haskellish way, rather than solving it in another language and then translating. -- Ben

On Tuesday 12 October 2004 5:20 pm, Ben Rudiak-Gould wrote: [ snip -- thanks for the examples and discussion ]
1. Try replacing implementation inheritance with containment and delegation when you translate to Haskell.
I'm not sure I understand what you mean by containment and delegation -- could you elaborate?
2. Try revisiting the original problem and thinking about how to solve it in a Haskellish way, rather than solving it in another language and then translating.
Thats exactly what I'm trying to do here :-) I've thought of having a type that basically stores a bunch of functions -- an implementation would simply provide an instance of that type with the functions, maybe.

At 01:19 17/10/04 -0500, John Goerzen wrote:
2. Try revisiting the original problem and thinking about how to solve it in a Haskellish way, rather than solving it in another language and then translating.
Thats exactly what I'm trying to do here :-) I've thought of having a type that basically stores a bunch of functions -- an implementation would simply provide an instance of that type with the functions, maybe.
That's what I've typically ended up doing in my code. #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

John Goerzen wrote:
I'm not sure I understand what you mean by containment and delegation -- could you elaborate?
This means that instead of inheriting all the member functions of the base class and selectively overriding them, you store an object of the "base" class as a member of the "derived" class, and make use of it in your implementation. The standard C++ ColoredPoint example looks like this if you use interface inheritance: class ColoredPoint : public Point { int color; public: // ColoredPoint-specific methods }; and like this if you use C&D: class ColoredPoint { Point p; // "containment" int color; public: int getX() { return p.getX(); } // "delegation" void setX(int x) { p.setX(x); } // ... // ColoredPoint-specific methods }; If you want to take advantage of inheritance polymorphism with this scheme, then you create an interface IPoint with virtual methods like getX and setX, and have both Point and ColoredPoint implement it (by inheriting it, in C++).
2. Try revisiting the original problem and thinking about how to solve it in a Haskellish way, rather than solving it in another language and then translating.
Thats exactly what I'm trying to do here :-) I've thought of having a type that basically stores a bunch of functions -- an implementation would simply provide an instance of that type with the functions, maybe.
Yes, this is often a good approach, especially when you combine it with labelled constructor fields. -- Ben

Haskell type classes don't really behave as one might expect coming from an OO perspective; cf. http://www.ninebynine.org/Software/Learning-Haskell-Notes.html#type-class-mi... That commentary doesn't say anything about interface inheritance. I don't offhand have a good answer for that question. In my own code, I guess I kind-of work around that issue. As for inheritamnce of implementation, I guess that can be done "by hand", by building a new type that contains the "base" type. #g -- At 18:32 12/10/04 +0000, John Goerzen wrote:
OK, recently I posed a question about rethinking some OO idioms, and that spawned some useful discussion.
I now have a followup question.
One of the best features of OO programming is that of inheritance. It can be used to slightly alter the behavior of objects without requiring modification to existing code or breaking compatibility with existing APIs.
As an example, say I have a ConfigParser class. This class can read in configuration files, provides various get/set methods to access them, and can write them back out.
Now say I would like to make this a little more powerful. Maybe I want to support the use of environment variables in my config file, so if there's a reference to $FOO in the file, it will be replaced by the contents of $FOO in the environment.
In OO, I would make a new EnvConfigParser class. I'd override the read() method. My new read() would probably start by calling the parent's read() method, to get parsing for free. Then it could iterate over the data, doing its environment variable substitution.
Now, in Haskell, we obviously have no objects like this. We do have something that provides some of the same benefits -- typeclasses. However, from what I can determine, they don't support algorithm inheritance like objects do in an OOP. Specifically, it seems impossible to have two instances of a single typeclass that work on the same type, while having one share most of the code with the other.
I'm wondering if there is a Haskell design pattern that I'm missing that would provid ethe kind of benefits that one gets from inheritance in the OO world.
-- John
-- John Goerzen Author, Foundations of Python Network Programming http://www.amazon.com/exec/obidos/tg/detail/-/1590593715
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

In message
OK, recently I posed a question about rethinking some OO idioms, and that spawned some useful discussion.
I now have a followup question.
One of the best features of OO programming is that of inheritance. It can be used to slightly alter the behavior of objects without requiring modification to existing code or breaking compatibility with existing APIs.
Closures can do this: // in C++/Java class ConfigParser { void read (String); int getFoo (String); } -- in Haskell data ConfigParser = ConfigParser { read :: String -> IO ConfigParser getFoo :: String -> Int } This is a structure of functions. The difference from C++/Java style objects is that this gives us object based polymorphism rather than class based polymorphism. Because they are Haskell closures rather than C-style functions they can hold private state by using partial application. configParser :: ConfigParser configParser = ConfigParser { read input = ... getFoo = ... } envConfigParser :: ConfigParser envConfigParser = configParser { read input = do env <- getEnvVars read configParser (substEnvVars input) } Duncan

The only problem with this is "name".
It is too easy to have naming clash in haskell. Field selectors are also
top-level functions and they shared the same namespace with other
functions.
for any reasonable scale program, we'll end up with ModuleA.read x,
ModuleB.read b. (Yes, we can alias the modules as A and B, but then we'll
have to face the module alias naming clash again)
In java/c++, we can name a method in the most meaningful and natural way we
like, rest-assured it won't have a problem just because some other
class/interface happens to use the same name for a different thing.
Plus, module, in my opinion is a logical functionality group, a quite
coarse-grained facility. not an appropriate tool to disambiguate names in a
fine-grained way.
I like the <<Lightweight Extensible Records for Haskell >> paper by Mark
Jones and Simon P. Jones. Very clean IMHO.
Not sure why it did not get implemented.
Duncan Coutts
OK, recently I posed a question about rethinking some OO idioms, and that spawned some useful discussion.
I now have a followup question.
One of the best features of OO programming is that of inheritance. It can be used to slightly alter the behavior of objects without requiring modification to existing code or breaking compatibility with existing APIs.
Closures can do this: // in C++/Java class ConfigParser { void read (String); int getFoo (String); } -- in Haskell data ConfigParser = ConfigParser { read :: String -> IO ConfigParser getFoo :: String -> Int } This is a structure of functions. The difference from C++/Java style objects is that this gives us object based polymorphism rather than class based polymorphism. Because they are Haskell closures rather than C-style functions they can hold private state by using partial application. configParser :: ConfigParser configParser = ConfigParser { read input = ... getFoo = ... } envConfigParser :: ConfigParser envConfigParser = configParser { read input = do env <- getEnvVars read configParser (substEnvVars input) } Duncan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe This message is intended only for the addressee and may contain information that is confidential or privileged. Unauthorized use is strictly prohibited and may be unlawful. If you are not the intended recipient, or the person responsible for delivering to the intended recipient, you should not read, copy, disclose or otherwise use this message, except for the purpose of delivery to the addressee. If you have received this email in error, please delete and advise the IT Security department at ITSEC@combined.com immediately

John Goerzen wrote:
One of the best features of OO programming is that of inheritance. ...
Oleg, Keean and me have lying around a draft that adds to this discussion. We reconstruct OCaml's tutorial in Haskell The short paper version is online and under consideration for FOOL: http://homepages.cwi.nl/~ralf/OOHaskell/ This work takes advantage of the HList library. I'll attach some code related to inheritance. So Haskell is an OOPL. Ralf {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} -- In the following, we refer to the tutorial "Objects in Caml" -- http://caml.inria.fr/ocaml/htmlman/manual005.html -- 3.2 Reference to self module SelfObj where import CommonMain hiding (HDeleteMany, hDeleteMany, TypeCast,typeCast) import GhcSyntax import GhcExperiments import TypeEqBoolGeneric import TypeEqGeneric1 import TypeCastGeneric2 import Label2 import Data.STRef import Data.IORef import Control.Monad.ST import Control.Monad.Fix infixr 9 # m # field = (m .!. field) -- A name space for record labels data MyNS = MyNS l_get_x = firstLabel MyNS "get-x" l_move = nextLabel l_get_x "move" l_field_x = nextLabel l_move "field x" l_print = nextLabel l_field_x "print" {- Ocaml Tutorial: 3.2 Reference to self A method or an initializer can send messages to self (that is, the current object). For that, self must be explicitly bound, here to the variable s (s could be any identifier, even though we will often choose the name self. class printable_point x_init = object (s) val mutable x = x_init method get_x = x method move d = x <- x + d method print = print_int s#get_x end;; let p = new printable_point 7;; val p : printable_point = <obj> p#print;; 7- : unit = () -} class_printable_point x_init self = do x <- newIORef x_init return $ l_field_x .=. x .*. l_get_x .=. readIORef x .*. l_move .=. (\d -> do{v<-readIORef x; writeIORef x (d + v)}) .*. l_print .=. ( (self # l_get_x ) >>= print ) .*. emptyRecord testp1 = do print "testp1" -- Note that 'mfix' plays the role of 'new' in the OCaml code... p <- mfix (class_printable_point 7) p # l_get_x >>= print p # l_move $ 2 p # l_get_x >>= print p # l_print -- Note, the latter prints the state of the mutated obj! print "OK" {- Ocaml Tutorial: 3.7 Inheritance We illustrate inheritance by defining a class of colored points that inherits from the class of points. This class has all instance variables and all methods of class point, plus a new instance variable c and a new method color. class colored_point x (c : string) = object inherit point x val c = c method color = c end;; let p' = new colored_point 5 "red";; val p' : colored_point = <obj> p'#get_x, p'#color;; - : int * string = (5, "red") -} -- Inheritance is simple: just adding methods... l_color = nextLabel l_print "color" class_colored_point x_init color self = do p <- class_printable_point x_init self return $ l_color .=. (return color) .*. p testp2 = do print "testp2" -- Note that 'mfix' plays the role of 'new' in the OCaml code... p <- mfix (class_printable_point 7) p' <- mfix (class_colored_point 5 "red") do{ x <- p' # l_get_x; c <- p' # l_color; print (x,c) } print "OK" {- Ocaml Tutorial: 3.4 Virtual methods It is possible to declare a method without actually defining it, using the keyword virtual. ... class virtual abstract_point x_init = object (self) val mutable x = x_init method virtual get_x : int method get_offset = self#get_x - x_init method virtual move : int -> unit end;; class point x_init = object inherit abstract_point x_init method get_x = x method move d = x <- x + d end;; -} l_offset = nextLabel l_color "offset" -- Note, compared with printable_point, the we just removed the field l_get_x -- That made the class uninstantiatable! -- No need for any a language extension for virtual, abstract. class_abstract_printable_point x_init self = do x <- newIORef x_init return $ l_field_x .=. x .*. l_offset .=. ((self # l_get_x ) >>= (\v -> return$ v - x_init)) .*. l_print .=. ( (self # l_get_x ) >>= print ) .*. emptyRecord class_concrete_printable_point x_init self = do p <- class_abstract_printable_point x_init self -- inherit... return $ -- add the missing (pure virtual) methods l_get_x .=. (readIORef (self # l_field_x)) .*. l_move .=. (\d -> do{v<-readIORef (self # l_field_x); writeIORef (self # l_field_x) (d + v)}) .*. p testp3 = do print "testp3" -- Note, if the latter is uncommented; we get the -- desired instantiation error. p <- mfix (class_concrete_printable_point 7) p # l_get_x >>= print p # l_move $ 2 p # l_offset >>= print p # l_get_x >>= print p # l_print print "OK"

Some people say that ocaml's object system is kinda useless. The best support I hear so far was:"it does not hurt" implementation inheritance, the strange "#" syntax, virtual method, why do I need them? In Java, people are doing programming-against-interface, implementation injection etc. All these show that we don't need implementation inheritance to be OO, and implementation inheritance is in many cases bad practice anyway. As somebody pointed out, we could do interface in Haskell with record. The only problem is names. If we could, as we can in OO languages, provide a separate namespace for the fields of each record. We are pretty much done. The rest is some kind of record coersion+row polymorphism mechanism. If haskell can do what Simon P. Jones and Mark Jones described in the paper <<Lightweight Extensible Records for Haskell>>, I'd say it is a already a nice functional OO language. Compared to Ocaml, 'OO' support is seamlessly integrated with the functional part. It leaves no redundancy, no overlapping in the language. In short, what if we don't create an object piece that competes with the functional part, but fix and enhance the record system that we currently have? Ben. This message is intended only for the addressee and may contain information that is confidential or privileged. Unauthorized use is strictly prohibited and may be unlawful. If you are not the intended recipient, or the person responsible for delivering to the intended recipient, you should not read, copy, disclose or otherwise use this message, except for the purpose of delivery to the addressee. If you have received this email in error, please delete and advise the IT Security department at ITSEC@combined.com immediately

Ben.Yu@combined.com wrote:
Some people say that ocaml's object system is kinda useless. The best support I hear so far was:"it does not hurt"
Why do you (or do these people) think having all the OO idioms of OCaml (see OCamls OO tutorial) is useless? Or do you mean too baroque? If not, what's missing?
implementation inheritance, the strange "#" syntax, virtual method, why do I need them?
Fine with me. OOHaskell doesn't need them, indeed.
In Java, people are doing programming-against-interface, implementation injection etc. All these show that we don't need implementation inheritance to be OO, and implementation inheritance is in many cases bad practice anyway.
Well having no implementation inheritance in Java would be a pretty brave limitation. Anyhow, OOHaskell (and OCaml) has programming-against-interface as well. Some related snippet from the OCaml tutorial. {- A point and a colored point have incompatible types, since a point has no method color. However, the function get_x below is a generic function applying method get_x to any object p that has this method (and possibly some others, which are represented by an ellipsis in the type). Thus, it applies to both points and colored points. let get_succ_x p = p#get_x + 1;; val get_succ_x : < get_x : int; .. > -> int = <fun> get_succ_x p + get_succ_x p';; - : int = 8 -} The corresponding OOHaskell snippet testp2 = do print "testp2" -- Note that 'mfix' plays the role of 'new' in the OCaml code... p <- mfix (class_printable_point 7) p' <- mfix (class_colored_point 5 "red") do{ x <- p' # l_get_x; c <- p' # l_color; print (x,c) } let get_succ_x obj = obj # l_get_x >>= (return . (+ 1)) get_succ_x p >>= print get_succ_x p' >>= print print "OK"
As somebody pointed out, we could do interface in Haskell with record. The only problem is names. If we could, as we can in OO languages, provide a separate namespace for the fields of each record. We are pretty much done.
Have you seen HList? There are 4 different solutions for first-class labels in the distribution.
The rest is some kind of record coersion+row polymorphism mechanism.
Yes, good point. That's what we meant: the object system in Haskell has been overlooked.
If haskell can do what Simon P. Jones and Mark Jones described in the paper <<Lightweight Extensible Records for Haskell>>, I'd say it is a already a nice functional OO language.
It can readily do more than that: http://www.cwi.nl/~ralf/HList
Compared to Ocaml, 'OO' support is seamlessly integrated with the functional part. It leaves no redundancy, no overlapping in the language.
What are you referring to? I mean: where is OO support seamlessly integrated with the functional part? Do you refer to OOHaskell?
In short, what if we don't create an object piece that competes with the functional part, but fix and enhance the record system that we currently have?
... or just exploit heterogeneous collections. Ralf

Why do you (or do these people) think having all the OO idioms of OCaml (see OCamls OO tutorial) is useless? Or do you mean too baroque? If not, what's missing?
Because it does not give us much that we cannot do nicely with the current functional part. separate name space of course. But it does not seem obvious that the rest of the object piece is necessary. Anything missing? Can't think of one. Simplicity I guess.
implementation inheritance, the strange "#" syntax, virtual method, why do I need them?
Fine with me. OOHaskell doesn't need them, indeed.
Nice.
Well having no implementation inheritance in Java would be a pretty brave limitation. Anyhow, OOHaskell (and OCaml) has programming-against-interface as well.
It may be. But is it a brave limitation that Haskell does not have implementation inheritance? I don't see the absolute need for impl-inheritance in an already rich and integral language such as Haskell. If impl-inheritance is already an arguable feature in OO langauges, I guess more thought should be given before it is pushed into a functional language at the cost of language complexity. (All I'm saying is general concern, it does not refer to HList or OOHaskell because I have no knowledge about them)
Have you seen HList? There are 4 different solutions for first-class labels in the distribution.
No. I'm just throwing in some ideas. If it is irrelavant or something already done, my apology. :) But, hey, don't get me wrong. I have no problem to see the language supporting impl-inheritance and other OO features. What I'm against is to invent a whole new standalone object system like what Ocaml has. In other words, it should not double the size of the language.
The rest is some kind of record coersion+row polymorphism mechanism.
Yes, good point. That's what we meant: the object system in Haskell has been overlooked.
If haskell can do what Simon P. Jones and Mark Jones described in the
Haskell 98 does not have row-polymorphism, does it? Or am I overlooking something? paper
<<Lightweight Extensible Records for Haskell>>, I'd say it is a already a nice functional OO language.
It can readily do more than that: http://www.cwi.nl/~ralf/HList
Compared to Ocaml, 'OO' support is seamlessly integrated with the functional part. It leaves no redundancy, no overlapping in the language.
What are you referring to? I mean: where is OO support seamlessly integrated with the functional
Thanks. I'll certainly find some time to digest it. part?
Do you refer to OOHaskell?
No. I did not look at OOHaskell yet. What I mean by seamless is the 'extensible record' proposal. It is not created for OO, but it can be used to do OO. Whatever I do, it is just an orthogonal piece of facility. While Ocaml objects and functional part don't look quite orthogonal. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe This message is intended only for the addressee and may contain information that is confidential or privileged. Unauthorized use is strictly prohibited and may be unlawful. If you are not the intended recipient, or the person responsible for delivering to the intended recipient, you should not read, copy, disclose or otherwise use this message, except for the purpose of delivery to the addressee. If you have received this email in error, please delete and advise the IT Security department at ITSEC@combined.com immediately

At 22:17 13/10/04 +0200, Ralf Laemmel wrote:
John Goerzen wrote:
One of the best features of OO programming is that of inheritance. ...
Oleg, Keean and me have lying around a draft that adds to this discussion. We reconstruct OCaml's tutorial in Haskell The short paper version is online and under consideration for FOOL: http://homepages.cwi.nl/~ralf/OOHaskell/ This work takes advantage of the HList library.
I'll attach some code related to inheritance. So Haskell is an OOPL.
I think that's interesting as a theoretical exercise, but I don't currently see myself using that framework in practice, in the form presented. As you say "Simply syntactic sugar would make OOP more convenient in Haskell." It is encouraging to see that the OO structures can be constructed within the Haskell type system. Would it simplify your approach significantly to focus on non-mutable objects? (In recent discussions with a colleague who implements complex systems in Java, he has observed that their systems are easier to understand and maintain when they elect to use non-mutable objects.) #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

Graham Klyne wrote:
At 22:17 13/10/04 +0200, Ralf Laemmel wrote:
... We reconstruct OCaml's tutorial in Haskell ,,,
I think that's interesting as a theoretical exercise, but I don't currently see myself using that framework in practice, in the form presented. As you say "Simply syntactic sugar would make OOP more convenient in Haskell."
Just for clarity ... As Oleg said, we would like to refrain from judgements regarding - OO in general - the urgency of combining all of OO with FP - the urgency of the combination in the case of Haskell. We have (varying) opinions about that ... but the OOHaskell effort is about showing that Haskell readily comes with an object system, or the ability to express it. That's it! At a more arbitrary level, we opted for an OCamlish object system because OCaml's system is definitely a good benchmark in terms of the many idioms covered. It is also a rewarding approach because OCaml's relies on non-trivial language extension, where our OOHaskell approach uses Haskell's existing type system to bring OO to Haskell. This is very, very rewarding for Haskell aficionados, indeed. We are also looking at OHaskell, Haskell++ and others, whose publicaly available examples should eventually become available for OOHaskell as well. When we think of syntactic sugar then this is merely about keywords such as class, interface, begin, end, method, ..., which some people might ask for anyway. With an OO hat one, people might want to really "see" the different forms of absractions methods, mutable fields, classes, mixins, while from an FP point of view functions and records are totally sufficient. Anyway, some of these keywords can be provided quite conveniently just as combinators. These combinators would then perform additional type-level checks or they are just NO-OPs. Personally, I wouldn't want any syntax extension. To summarise, what's very important in our view is that OOHaskell shows that no language extension is needed to bring OO to Haskell. And even in the case where we end up providing syntactic sugar then this is about surface syntax whose reduction to normal Haskell syntax is a *local structural mapping* as it could be peformed by the most trivial preprocessor or macro system. So the type system of Haskell is fit for OO. That's cool. From a practical perspective, the foundation of OOHaskell to depend on HList implies that type errors are potentially inconvenient depending in turn on encoding details of the type-level code. For example, it takes some coding effort to teach the type-level implementation such that you see type errors that are anywhere close "class a found but class b required" or "class a is not a subclass of class b". The HList paper discusses some idiom for better type error messages in type-level code. A mail by Oleg on keyword arguments discusses another idiom, a CPS-like trick, but there is more work to be done.
It is encouraging to see that the OO structures can be constructed within the Haskell type system.
Absolutely.
Would it simplify your approach significantly to focus on non-mutable objects? (In recent discussions with a colleague who implements complex systems in Java, he has observed that their systems are easier to understand and maintain when they elect to use non-mutable objects.)
Again, we leave it to others to make choices. If we wouldn't present the details of mutable projects, Haskell object system will be claimed to be incomplete, which it is not :-) Ralf http://homepages.cwi.nl/~ralf/

Looks like my worry is pointless. :->
I was just afraid that Haskell may pick up another object monster. (And I'm
a C++/Java programmer)
Although I still miss a simple primitive language construct to do
'extensible record', it is definitely a nice work both theoretically and
practically to present an OO library.
And I'm totally with you guys about 'leaving choices to others'. My belief
is: the more orthogonal, the better.
Cheers,
Ben.
Ralf Laemmel
At 22:17 13/10/04 +0200, Ralf Laemmel wrote:
... We reconstruct OCaml's tutorial in Haskell ,,,
I think that's interesting as a theoretical exercise, but I don't currently see myself using that framework in practice, in the form presented. As you say "Simply syntactic sugar would make OOP more convenient in Haskell."
Just for clarity ... As Oleg said, we would like to refrain from judgements regarding - OO in general - the urgency of combining all of OO with FP - the urgency of the combination in the case of Haskell. We have (varying) opinions about that ... but the OOHaskell effort is about showing that Haskell readily comes with an object system, or the ability to express it. That's it! At a more arbitrary level, we opted for an OCamlish object system because OCaml's system is definitely a good benchmark in terms of the many idioms covered. It is also a rewarding approach because OCaml's relies on non-trivial language extension, where our OOHaskell approach uses Haskell's existing type system to bring OO to Haskell. This is very, very rewarding for Haskell aficionados, indeed. We are also looking at OHaskell, Haskell++ and others, whose publicaly available examples should eventually become available for OOHaskell as well. When we think of syntactic sugar then this is merely about keywords such as class, interface, begin, end, method, ..., which some people might ask for anyway. With an OO hat one, people might want to really "see" the different forms of absractions methods, mutable fields, classes, mixins, while from an FP point of view functions and records are totally sufficient. Anyway, some of these keywords can be provided quite conveniently just as combinators. These combinators would then perform additional type-level checks or they are just NO-OPs. Personally, I wouldn't want any syntax extension. To summarise, what's very important in our view is that OOHaskell shows that no language extension is needed to bring OO to Haskell. And even in the case where we end up providing syntactic sugar then this is about surface syntax whose reduction to normal Haskell syntax is a *local structural mapping* as it could be peformed by the most trivial preprocessor or macro system. So the type system of Haskell is fit for OO. That's cool. From a practical perspective, the foundation of OOHaskell to depend on HList implies that type errors are potentially inconvenient depending in turn on encoding details of the type-level code. For example, it takes some coding effort to teach the type-level implementation such that you see type errors that are anywhere close "class a found but class b required" or "class a is not a subclass of class b". The HList paper discusses some idiom for better type error messages in type-level code. A mail by Oleg on keyword arguments discusses another idiom, a CPS-like trick, but there is more work to be done.
It is encouraging to see that the OO structures can be constructed within the Haskell type system.
Absolutely.
Would it simplify your approach significantly to focus on non-mutable objects? (In recent discussions with a colleague who implements complex systems in Java, he has observed that their systems are easier to understand and maintain when they elect to use non-mutable objects.)
Again, we leave it to others to make choices. If we wouldn't present the details of mutable projects, Haskell object system will be claimed to be incomplete, which it is not :-) Ralf http://homepages.cwi.nl/~ralf/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe This message is intended only for the addressee and may contain information that is confidential or privileged. Unauthorized use is strictly prohibited and may be unlawful. If you are not the intended recipient, or the person responsible for delivering to the intended recipient, you should not read, copy, disclose or otherwise use this message, except for the purpose of delivery to the addressee. If you have received this email in error, please delete and advise the IT Security department at ITSEC@combined.com immediately
participants (7)
-
Ben Rudiak-Gould
-
Ben Rudiak-Gould
-
Ben.Yu@combined.com
-
Duncan Coutts
-
Graham Klyne
-
John Goerzen
-
Ralf Laemmel