[Haskell-cafe] default function definitions

Patrick Browne patrick.browne at dit.ie
Sat Jul 24 13:59:26 EDT 2010


Hi,
I am studying the Haskell type class system as part of a language
comparison thesis. At this point I am looking at how default function
definitions are handled in classes. Functions are usually defined in
instances, not classes. I appreciate that the code below may not be an
appropriate way to write Haskell programs, but it does help me
understand how defaults work. I am not trying to construct a running
program. Any feedback on the questions below and defaults work in
general would be appreciated.

Pat

module A where
data Person = Person String Integer deriving Show
data Employee  = Employee String Integer deriving Show

class C1 c1 where
  age :: c1 -> Integer
-- add default impl, can this be defined only once at class level?
-- Can this function be redefined in a *class* lower down the heirarchy?
 age(c1) = 1


-- Is it true that instances must exists before we can run function or
make subclasses?
instance C1  Person where
instance C1  Employee where


-- Is it true that C2 can inherit age, provided an instance of C1 exists
class C1 c2 =>  C2 c2 where
  name :: c2 -> String
  name(c2) = "C2"


instance C2  Person where
instance C2  Employee where

-- Is it true that C3 cannot override C1 or C2 existing defaults?
-- Is it true that this must be done at instance level?
-- class Cx c3 =>  C3 c3 where
--    age(c3) = 3
--

This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie


More information about the Haskell-Cafe mailing list