[Haskell-cafe] [Newbie] Quest for inheritance

Gracjan Polak gracjan at acchsh.com
Sun Jun 5 13:55:31 EDT 2005


Cédric Paternotte wrote:
 > Hi. This is my first message here so Hello to everyone.
 >
 > I'm just starting to learn Haskell and I really think it's a cool 
language.

Me too :)

 > I know OO and inheritance is not really the point of Haskell and that
 > other mechanisms are provided to somewhat achieve reuse. But it's a
 > way of programming I've been so used to that I feel lost without it.
 > You might think I'm heading in the wrong direction. My mistake I have
 > to agree. Let's take it as a learning exercise then.

Me too :)

 > 5. With this : 
http://www.cs.utexas.edu/ftp/pub/techreports/tr01-60/tr01-60.pdf
 >

I've been thinking about slight generalization of this lately. Here are 
my semi-backed thoughts as of now.

First of all, in Haskell there will be strict separation between 
interfaces and data, so almost every method will be declared twice. This 
is not so strange to anybody programing in Java, but for C++ programmers 
can be. Inheritance relation is specified after data. There is also 
separation between two concepts: what interfaces each piece of data 
implements and which intefaces given interface inherits. So:

{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module Main where

-- general inheritance relation
class Inherits b x where
     get_super :: x -> b

-- declare interface with one method
class IA a where
     get_a :: a -> Int

-- define data with one field
data DA = DA { da_field :: Int }

-- say how data DA conforms to interface IA
instance IA DA where
     get_a x = da_field x

-- declare some other interface IB
-- note: IB is unrelated to IA
class IB a where
     get_b :: a -> String

-- data that inherits fields of DA and adds one another field
data DB = DB { db_super :: DA, db_field :: String }

-- DB inherits fields and methods of DA
instance Inherits DA DB where
     get_super x = db_super x

-- data DB implements interface IB
instance IB DB where
     get_b x = db_field x

-- some other random data
data DC = DC { dc_super :: DA }

-- DC implements interface IB
instance IB DC where
     get_b x = show (get_a x)

-- and inherits DA
instance Inherits DA DC where
     get_super x = dc_super x

-- now the tricky part: state that every data x inheriting DA
-- implements all interfaces of DA (repeat for each interface)
instance (Inherits DA x) => IA x where
     get_a w = da_field (get_super w)

main = do
     let db = DB (DA 123) "zzz"
     let dc = DC (DA 123)
     putStrLn $ show (get_a db)
     putStrLn $ show (get_a dc)
     putStrLn $ show (get_b db)
     putStrLn $ show (get_b dc)

As you see there is much more writting as in Java. But this gives better 
control over inheritance and subsumption because everything must be 
stated explicitly. Multiple inheritance is allowed :) Also it is 
"private inheritance" (as in C++) by default.

There are some problems left: how to update a field? or how to make 
inheritance transitive. I don't know it yet :)

 >
 > I guess my question now is this : Are there other ways to achieve
 > inheritance in Haskell ?

Me too:)

My proposal (above) is about the level of 'OO' things done in procedural 
languages (example: C with GTK+ library). There must be a better way. 
Any comments?

-- 
Gracjan


More information about the Haskell-Cafe mailing list