[Haskell-cafe] Simulating OO programming with type classes; writing a factory fu nction

Bayley, Alistair Alistair_Bayley at ldn.invesco.com
Tue May 31 11:16:34 EDT 2005


I've been experimenting with simulating OO programming in Haskell (why, you
might ask? Because I'm trying to port a non-trivial piece of software, and I
want to respect the original design, at least to begin with). I've been
trying the technique illustrated by Ralf Laemmel:
  http://homepages.cwi.nl/~ralf/OOHaskell/src/interpreter/extensible.hs

There's a small problem: how to write a factory function that returns values
of various subtypes. The makeSubType function below won't compile, obviously
because the returns types are different (they're not the same 'm'). I
realise that I'm looking for something that Haskell doesn't natively do, so
my question is: is there some kind of workaround that'll give me the ability
to write factory functions?

(No doubt there's some obvious trick that I've missed :-)

I'm aware of http://homepages.cwi.nl/~ralf/OOHaskell/ , which will be my
technique of last resort. I was fond of Ralf's extensible interpreter
example because it's quite lightweight, but if there's no way around the
factory problem, so be it.

Alistair.


-------------------------------------------
-- Toy OO example with subtyping

module Main where

main = print "boo"

-- class to represent OO base class
class BaseClass c

-- each subtype of BaseClass is a separate datatype
data SubBase1 = SubBase1 Int
data BaseClass c => SubBase2 c = SubBase2 c

instance BaseClass SubBase1
instance BaseClass (SubBase2 c)


-- methods of BaseClass defined with new class

class BaseClass c => Method c where
  -- illegal: can't return values of type c; can only consume them
  method1 :: c -> Int -> c
  method2 :: c -> Int

-- install each subtype (datatype) as instance of Method

instance Method SubBase1 where
  method1 _ i = SubBase1 i
  method2 (SubBase1 i) = i

instance Method c => Method (SubBase2 c) where
  -- This one fails, because must return polymorphic value, not concrete
  --method1 _ i = SubBase2 (SubBase1 5)
  method1 x i = x
  method2 x = 2

-- Also, cannot make factory function:

--makeSubType :: (Method m) => String -> m
makeSubType s =
  if s == "SubBase1"
  then SubBase1 3
  else SubBase2 (SubBase1 4)

-----------------------------------------
*****************************************************************
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.
*****************************************************************



More information about the Haskell-Cafe mailing list