[Haskell-cafe] data type declaration

Patrick Browne patrick.browne at dit.ie
Sat Jul 24 17:53:45 EDT 2010


Hi,
I am trying to understand the data type declaration below.
What is the relation between class C3 and the data type Address below?
Where is such a technique used?

Thanks,
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

instance C1  Person where
   age(Person "P1" 1) = 1


instance C1  Employee where
    age(Employee "E1" 1) = 1


class C1 c2 =>  C2 c2 where
  name :: c2 -> String


instance C2  Person where
      name(Person "P2" 1) = "P2"

instance C2  Employee where
    name(Employee "E2" 1) = "E2"


class C2 c3 =>  C3 c3 a where
  address :: c3  -> a

instance C3 Person String where

-- ** What are the semantics or purpose of this construct.
-- ** Is the type declared in the context of a class.
data C3 c3 a  => Address c3 a = Address c3 a

instance C3 Person (Address String String) where

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