[Haskell-cafe] [Newbie] Quest for inheritance

Cédric Paternotte cpaternotte at gmail.com
Mon Jun 6 06:52:25 EDT 2005


Hi Gracjan,

On 6/5/05, Gracjan Polak <gracjan at acchsh.com> wrote:
> 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:

I don't mind declaring functions headers more than once as long as I
don't have to do it with their body.

> {-# 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)

This is smart. So I understand the point of this part is to forward
the "function call" to the parent (through get_super). All you have to
do is to define these forwards in each inheriting data.

Does it also mean that, in each inheriting data, you have to define
these forwards to all your parents (meaning not only to the one just
above, but all of them) ? In other words if I was to define a data DD
which inherits from DB (and thus also from DA), will I have to define
forwards for both get_a and get_b ? If not, how would you declare it ?

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

I think I like this way of dealing with inheritance. There's a bit
more typing indeed and it's kind of limited but it has the advantage
of being relativily simple to put in action.
What I really like with this is that you can come up with new data
types inheriting DA without having to change anything in the
declaration of DA.

I guess you'd just better avoid having too many levels of hierarchy as
it tends to get more and more verbose ;)

Cédric


More information about the Haskell-Cafe mailing list