
Bulat Ziganshin wrote:
http://haskell.org/haskellwiki/OOP_vs_type_classes although i mentioned not only pluses but also drawbacks of type classes: lack of record extension mechanisms (such at that implemented in O'Haskell) and therefore inability to reuse operation implementation in an derived data type...
Hi Bulat - You can reuse ops in a derived data type but it involves a tremendous amount of boilerplate. Essentially, you just use the type classes to simulate extendable records by having a method in each class that accesses the fixed-length record corresponding to that particular C++ class. Here is an example (apologies for the length!) which shows a super class function being overridden in a derived class and a derived class method (B::Extra) making use of something implemented in the super class: module Main where {- Haskell translation of the following C++ class A { public: String s; Int i; A(String s, Int i) s(s), i(i){} virtual void Display(){ printf("A %s %d\n", s.c_str(), i); } virtual Int Reuse(){ return i * 100; } }; class B: public A{ public: Char c; B(String s, Int i, Char c) : A(s, i), c(c){} virtual void Display(){ printf("B %s %d %c", s.c_str(), i, c); } virtual void Extra(){ printf("B Extra %d\n", Reuse()); } }; -} data A = A { _A_s :: String , _A_i :: Int } -- This could do arg checking etc constructA :: String -> Int -> A constructA = A class ClassA a where getA :: a -> A display :: a -> IO () display a = do let A{_A_s = s, _A_i = i} = getA a putStrLn $ "A " ++ s ++ show i reuse :: a -> Int reuse a = _A_i (getA a) * 100 data WrapA = forall a. ClassA a => WrapA a instance ClassA WrapA where getA (WrapA a) = getA a display (WrapA a) = display a reuse (WrapA a) = reuse a instance ClassA A where getA = id data B = B { _B_A :: A, _B_c :: Char } constructB :: String -> Int -> Char -> B constructB s i c = B {_B_A = constructA s i, _B_c = c} class ClassA b => ClassB b where getB :: b -> B extra :: b -> IO () extra b = do putStrLn $ "B Extra " ++ show (reuse b) data WrapB = forall b. ClassB b => WrapB b instance ClassB WrapB where getB (WrapB b) = getB b extra (WrapB b) = extra b instance ClassA WrapB where getA (WrapB b) = getA b display (WrapB b) = display b reuse (WrapB b) = reuse b instance ClassB B where getB = id instance ClassA B where getA = _B_A -- override the base class version display b = putStrLn $ "B " ++ _A_s (getA b) ++ show (_A_i (getA b)) ++ [_B_c (getB b)] main :: IO () main = do let a = constructA "a" 0 b = constructB "b" 1 '*' col = [WrapA a, WrapA b] mapM_ display col putStrLn "" mapM_ (putStrLn . show . reuse) col putStrLn "" extra b {- Output:
ghc -fglasgow-exts --make Main main A a0 B b1*
0 100 B Extra 100
-} (If the "caseless underscore" Haskell' ticket is accepted the leading underscores would have to be replaced by something like "_f" ie _A_s ---> _fA_s etc) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com