[Haskell-beginners] Equivalence of Inheritance

Bastian Erdnüß earthnut at web.de
Tue Dec 14 22:46:30 CET 2010


On Dec 14, 2010, at 19:11, Russ Abbott wrote:

> I'm also confused about how to do the equivalence of inheritance in Haskell.
> Here is a complete example below.  It doesn't compile. The error message
> is
> 
> Class `Person' used as a type
> 
> 
> If I write "(Person p) =>" instead, I get other diagnostics.
> 
> I would very much appreciate seeing how this should be done in Haskell.

What about

> ---------- Example (multiple files) ------------
> --- Group.hs ---
> module Group where
> 
> import Person
> 
> data Group = Group { members :: [Person] }
> 
> instance Show Group where
>  show group = unlines $ map show $ members group
> 
> --- Person.hs ---
> 
> module Person where
> 
> data Person = Person {
>  nameP :: p -> String ,
>  ageP :: p -> Int ,
>  getGenderSpecificCondition :: p -> Condition }
> 
> instance Show Person where
>  show p = nameP p ++ "(" ++ show (ageP p) ++ ", " ++
>             show (getGenderSpecificCondition p) ++ ")"
> 
> data Condition = Bad | OK | Good

 class PersonClass p where
   toPerson :: p -> Person

> --- Man.hs ---
> module Man where
> 
> import Person
> 
> data Man = Man { nameM :: String
>                , ageM  :: Int
>                , prostateCondition :: Condition
>                }
> 
> instance PersonClass Man where

>    toPerson (Man n a c) = Person n a c
> 
> --- Woman.hs---
> module Woman where
> 
> import Person
> 
> data Woman = Woman { nameW :: String
>                    , ageW  :: Int
>                    , ovaryCondition :: Condition
>                    }
> 
> instance Person Woman where

>    toPerson (Woman n a c) = Person n a c
> 
> ---------- End example (multiple files) ------------



More information about the Beginners mailing list