OO Design in Haskell Example (Draft)

In the last OO design in Haskell thread (and probably in every one preceeding it), it was suggested that having some examples might be a good idea. Since most people with existing designs will have some familiarity with Design Patterns, and those are typical building blocks for OO designs, it occured to me that implementing some of them might be a useful excersize. If for nothing other than learning some more Haskell. Now, some of them are probably bad ideas for implementing in Haskell. There's a better, or more natural, way than what is suggested by the design pattern. Visitor is probably not a good pattern to follow, for example. On the other hand, others may still be useful, even in a functional language. So, I've been working on a Composite example. I've used existential types to have a generic proxy to the base type, rather than a simple algebraic type, since adding new leaves to the algebraic type means modifying the whole type, a violation of the Open-Closed principle (open for extension, closed for modification) The interface of the composite. Two methods, add and draw.
class IComponent e where draw ::e -> String add :: (IComponent e') => e -> e' -> Component
A proxy type which can hold any kind of component, and provides the 'virtual' dispatch implementation. That is, it forwards to the add or draw implementation of the instance it is proxying for.
data Component = forall e.(IComponent e) => Component e
componentDraw :: Component -> String componentDraw (Component c) = draw c
componentAdd :: (IComponent e) => Component -> e -> Component componentAdd (Component e) a = Component (add e a)
instance IComponent Component where draw = componentDraw add = componentAdd
The Single type, which is the leaf node in this composite, add is a no-op, except for wrapping the value in a Component. Since there isn't an implicit down cast from the 'derived' Single to the 'base' Component.
data Leaf = Text String deriving(Show, Eq)
leafDraw :: Leaf -> String leafDraw (Text s) = show s
leafAdd :: (IComponent e) => Leaf -> e -> Component leafAdd s _ = Component s
instance IComponent Leaf where draw = leafDraw add = leafAdd
The Composite type, which holds a list of Components through the composite proxy. I was tempted to make the list a state variable, so that add could modify rather than produce a new Many, but I wanted to get the basics working.
data Composite = Many [Component]
compositeDraw :: Composite -> String compositeDraw (Many []) = "()" compositeDraw (Many leaves) = "(" ++ (foldr1 (++) $ map draw leaves) ++ ")"
compositeAdd :: (IComponent e) => Composite -> e -> Component compositeAdd (Many leaves) c = Component $ Many ((Component c) : leaves)
instance IComponent Composite where draw = compositeDraw add = compositeAdd

Steve Downey wrote:
So, I've been working on a Composite example. I've used existential types to have a generic proxy to the base type, rather than a simple algebraic type, since adding new leaves to the algebraic type means modifying the whole type, a violation of the Open-Closed principle (open for extension, closed for modification)
Rather than using existential types, a simple record of functions can be often be useful. ie: data Component = Component { draw :: String add :: Component -> Component } It might be worth comparing this approach with the (more complex) one you have described. Tim

Hello Tim, Monday, February 26, 2007, 2:26:44 AM, you wrote:
Rather than using existential types, a simple record of functions can be often be useful. ie:
data Component = Component { draw :: String add :: Component -> Component }
Steve, you can look at the pages http://haskell.org/haskellwiki/OOP_vs_type_classes http://haskell.org/haskellwiki/IO_inside which describes some alternatives to OO approach used in functional programming world and Haskell in partial. because first page is just about switching from OOP to Haskell, you may consider adding to this page patterns you've designed -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Tim Docker wrote:
Steve Downey wrote:
So, I've been working on a Composite example. I've used existential types to have a generic proxy to the base type, rather than a simple algebraic type, since adding new leaves to the algebraic type means modifying the whole type, a violation of the Open-Closed principle (open for extension, closed for modification)
Rather than using existential types, a simple record of functions can be often be useful. ie:
data Component = Component { draw :: String add :: Component -> Component }
It might be worth comparing this approach with the (more complex) one you have described.
The point about existential types is that every class like IComponent that allow as useful existential like data Component = forall e.(IComponent e) => Component e can be put into the record form Tim mentions. See the old wiki pages at http://haskell.org/hawiki/ExistentialTypes This is because every such IComponent has to look like class IComponent e where foo1 :: e -> ... -> e ... bar1 :: e -> ... ... where the dots in "-> ..." must not contain the type variable e. Regards, apfelmus

interesting. it leads to something that feels much more like an object
based, as opposed to a class based, system.
as far as haskell is concerned, everything has the same type, even
though different instances have very different behavior.
instance variables are captured by the closures that define the object
methods, through the instance construction functions.
i get the feeling that a model like 'self''s , based on prototypes,
would not be that hard to implement.
i should have the equivalent example with this style done soon.
the question is, which plays nicer with the rest of haskell? that is,
if i'm not committing to a closed dsl, which style is more likely to
be reusable against other libraries.
my experience so far has been with parsers and type checkers that make
extensive use of pattern matching, which is why I probably gravitated
towards the type class with existentials solution. but my experience
is limited.
On 2/26/07, apfelmus@quantentunnel.de
Tim Docker wrote:
Steve Downey wrote:
So, I've been working on a Composite example. I've used existential types to have a generic proxy to the base type, rather than a simple algebraic type, since adding new leaves to the algebraic type means modifying the whole type, a violation of the Open-Closed principle (open for extension, closed for modification)
Rather than using existential types, a simple record of functions can be often be useful. ie:
data Component = Component { draw :: String add :: Component -> Component }
It might be worth comparing this approach with the (more complex) one you have described.
The point about existential types is that every class like IComponent that allow as useful existential like
data Component = forall e.(IComponent e) => Component e
can be put into the record form Tim mentions. See the old wiki pages at
http://haskell.org/hawiki/ExistentialTypes
This is because every such IComponent has to look like
class IComponent e where foo1 :: e -> ... -> e ... bar1 :: e -> ... ...
where the dots in "-> ..." must not contain the type variable e.
Regards, apfelmus
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

interesting. it leads to something that feels much more like an object
as far as haskell is concerned, everything has the same type, even
Steve Downey wrote: based, as opposed to a class based, system. though different instances have very different behavior.
.... the question is, which plays nicer with the rest of haskell? that is, if i'm not committing to a closed dsl, which style is more likely to be reusable against other libraries.
I suspect there's no right answer - it's a case of choosing the best approach for the problem. As an example, my charting library (http://dockerz.net/software/chart.html) uses the record of functions approach for composing drawings: data Renderable = Renderable { minsize :: (Render RectSize) render :: (Rect -> Render ()) } Tim

The composite design pattern implemented using record types, where the named elements are the interface to the object Overall, I think I agree with Tim that the record types are simpler to code. I'm not sure, though, what would happen if I tried to add state to the types. With the previous example, using existentials to create a reference type that holds elements of a type class that matches the interface, I think that it would be natural to hold state by having that element stored in a mutable state variable, and replacing the held values. In any case: Two methods, add and draw
data Component = Component { draw :: String, add :: Component -> Component }
A constructor for the leaf type, which holds a string
leaf :: String -> Component leaf s = Component draw1 add1 where draw1 = show s add1 _ = leaf s
the draw method for the composite type (because I was having trouble with layout and formating for 72 cols)
compositeDraw :: [Component] -> String compositeDraw [] = "()" compositeDraw leaves = "(" ++ (foldr1 (++) $ map draw leaves) ++ ")"
A constructor for the composite type, which holds a list of components and dispatches to the contained elements
composite :: [Component] -> Component composite cs = Component draw1 add1 where draw1 = compositeDraw cs add1 c = composite $ c:cs
On 2/27/07, Tim Docker
interesting. it leads to something that feels much more like an object
as far as haskell is concerned, everything has the same type, even
Steve Downey wrote: based, as opposed to a class based, system. though different instances have very different behavior.
.... the question is, which plays nicer with the rest of haskell? that is, if i'm not committing to a closed dsl, which style is more likely to be reusable against other libraries.
I suspect there's no right answer - it's a case of choosing the best approach for the problem. As an example, my charting library (http://dockerz.net/software/chart.html) uses the record of functions approach for composing drawings:
data Renderable = Renderable { minsize :: (Render RectSize) render :: (Rect -> Render ()) }
Tim
participants (5)
-
apfelmus@quantentunnel.de
-
Bulat Ziganshin
-
Steve Downey
-
Tim Docker
-
Tim Docker