[Haskell-cafe] object oriented technique
Tad Doxsee
tad.doxsee at gmail.com
Thu Mar 31 08:54:00 CEST 2011
Tillmann,
Thank you for your detailed reply. It was a real eye opener. I
hadn't seen anything like that before.
It seems that your ShapeClass is very similar to, and plays the same
role as, the Class ShapeC from my example. I wonder if that was how
haskellers implemented shared functions before type classes were
invented.
One advantage that I see in your approach is that you only need one
function, "call", that can be used to dereference any method in
ShapeClass. In my example, I needed to define ShapeC ShapeD instances
for both draw and copyTo.
I suppose one nice aspect of using a type class is that the copyTo
method can be applied to a Rectangle to give another Rectangle, or to
a Circle, or to a generic ShapeD to give a generic ShapeD. The copyTo
function in your example produces a generic shape.
Thanks again for your help.
Tad
On Wed, Mar 30, 2011 at 2:57 AM, Tillmann Rendel
<rendel at informatik.uni-marburg.de> wrote:
> Hi,
>
> Steffen Schuldenzucker wrote:
>>
>> data Shape = Shape {
>> draw :: String
>> copyTo :: Double -> Double -> Shape
>> }
>
> Tad Doxsee wrote:
>>
>> Suppose that the shape class has 100 methods and that 1000 fully
>> evaluated shapes are placed in a list.
>
> The above solution would store the full method table with each object.
> Instead, we could share the method tables between objects. An object would
> then uniformly contain two pointers: One pointer to the method table, and
> one poiner to the internal state.
>
> {-# LANGUAGE ExistentialQuantification, Rank2Types #-}
>
> data Object methods = forall state . Object {
> methods :: methods state,
> state :: state
> }
>
> Calling a method requires dereferencing both pointers.
>
> call :: (forall state . methods state -> state -> a) ->
> (Object methods -> a)
> call method (Object methods state) = method methods state
>
>
> Using this machinery, we can encode the interface for shapes.
>
> data ShapeClass state = ShapeClass {
> draw :: state -> String,
> copyTo :: state -> Double -> Double -> Shape
> }
>
> type Shape = Object ShapeClass
>
>
> An implementation of the interface consists of three parts: A datatype or
> the internal state, a method table, and a constructor.
>
> data RectangleState = RectangleState {rx, ry, rw, rh :: Double}
>
> rectangleClass :: ShapeClass RectangleState
> rectangleClass = ShapeClass {
> draw = \r ->
> "Rect (" ++ show (rx r) ++ ", " ++ show (ry r) ++ ") -- "
> ++ show (rw r) ++ " x " ++ show (rh r),
> copyTo = \r x y -> rectangle x y (rw r) (rh r)
> }
>
> rectangle :: Double -> Double -> Double -> Double -> Shape
> rectangle x y w h
> = Object rectangleClass (RectangleState x y w h)
>
>
> The analogous code for circles.
>
> data CircleState = CircleState {cx, cy, cr :: Double}
>
> circleClass :: ShapeClass CircleState
> circleClass = ShapeClass {
> draw = \c ->
> "Circ (" ++ show (cx c) ++ ", " ++ show (cy c)++ ") -- "
> ++ show (cr c),
> copyTo = \c x y -> circle x y (cr c)
> }
>
> circle :: Double -> Double -> Double -> Shape
> circle x y r
> = Object circleClass (CircleState x y r)
>
>
> Rectangles and circles can be stored together in usual Haskell lists,
> because they are not statically distinguished at all.
>
> -- test
> r1 = rectangle 0 0 3 2
> r2 = rectangle 1 1 4 5
> c1 = circle 0 0 5
> c2 = circle 2 0 7
>
> shapes = [r1, r2, c1, c2]
>
> main = mapM_ (putStrLn . call draw) shapes
>
>
> While this does not nearly implement all of OO (no inheritance, no late
> binding, ...), it might meet your requirements.
>
> Tillmann
>
> PS. You could probably use a type class instead of the algebraic data type
> ShapeClass, but I don't see a benefit. Indeed, I like how the code above is
> very explicit about what is stored where. For example, in the code of the
> rectangle function, it is clearly visible that all shapes created with that
> function will share a method table.
>
More information about the Haskell-Cafe
mailing list