
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

Patrick Browne wrote:
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?
OK, let's see what we can come up with...
module A where data Person = Person String Integer deriving Show data Employee = Employee String Integer deriving Show
Person and Employee are identical types, just with different names.
class C1 c1 where age :: c1 -> Integer
The "age" function works for any type declared to be an instance of C1.
instance C1 Person where age(Person "P1" 1) = 1
instance C1 Employee where age(Employee "E1" 1) = 1
Person and Employee are both declared to be instances of C1. Incidentally, those declarations look *very* dubious. What the first one says, for example, is that if a person is called "P1" and their age is 1, then return 1. If the name is not "P1" or the age is not 1, crash.
class C1 c2 => C2 c2 where name :: c2 -> String
The "name" function works for any type declared to be an instance of C2. Any such type must also be an instance of C1.
instance C2 Person where name(Person "P2" 1) = "P2"
instance C2 Employee where name(Employee "E2" 1) = "E2"
Person and Employee are both instances of C2 (which is allowed, since they are already instances of C1). Again, the instance declarations look highly dubious.
class C2 c3 => C3 c3 a where address :: c3 -> a
This is not valid in Haskell '98. This is actually a type system extension known as "multi-parameter type classes", which do not even vaguely correspond to anything in normal OOP. (Except for being very slightly similar to generics, perhaps.) Here C3 is a relation *between* two types (type "c3" and type "a"). For any so-related types, the "address" fucntion can map one type to the other. (Presumably by returning the contents of an address field...) This is a very odd way to define such an action.
instance C3 Person String where
The types Person and String are related by C3 as described above. However, calling "address" will crash immediately (since no implementation is supplied).
-- ** 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
This defines a new type named "Address". The type has two type parameters ("c3" and "a"), and a value of this type has two fields. In other words, if you say "Address Rock Stone", then an Address value has two fields, the first one of type Rock, the second of type Stone. Also, the type parameters are required to be related by C3. So unless you write "instance C3 Rock Stone", you cannot say "Address Rock Stone". It would be a type error. However, since "instance C3 Person String" exists above, you may say "Address Person String".
instance C3 Person (Address String String) where
This says that the type "Person" and the type "Address String String" are related by C3 as well - which is amusing, given that "Address String String" is a type error due to the fact that we don't have "instance C3 String String"... In short, this big tangle of code shouldn't even compile, and if it does, I have no clue what in the name of God it actually does. It appears to have been written by somebody who has no idea what they're doing. If you want to know what a specific language construct does, or why you'd use it, or which way you'd attack a specific problem, I (and everybody else here) can try to offer some explanation. But the code you're showing me doesn't really make any sense.

On 25 July 2010 13:09, Andrew Coppin
This is not valid in Haskell '98. This is actually a type system extension known as "multi-parameter type classes", which do not even vaguely correspond to anything in normal OOP. (Except for being very slightly similar to generics, perhaps.)
Closest perhaps to multimethods in Cecil and and I think CLOS - though multimethods in CLOS does seem to take things far out into space with :before :after and :around.

Andrew, Thanks for your detailed feedback, it is a great help. I appreciate that the code does not do anything useful, nor is it an appropriate way to write Haskell, but it does help me understand language constructs. I have seen statements like
data C3 c3 a => Address c3 a = Address c3 a
and wondered what they mean and how could they be used. I am studying the Haskell type class system as part of a language comparison. I am trying to exercise and understand the constructs rather than develop a meaningful application. Perhaps I should have mentioned this in my post. Thanks again, Pat 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

Patrick Browne wrote:
Andrew, Thanks for your detailed feedback, it is a great help.
Well, I like to be helpful.
I appreciate that the code does not do anything useful, nor is it an appropriate way to write Haskell, but it does help me understand language constructs.
Personally, I find it easier to understand things when they do something meaningful, but sure.
I am studying the Haskell type class system as part of a language comparison. I am trying to exercise and understand the constructs rather than develop a meaningful application.
The best way to understand Haskell is... to completely forget everything you already know, and start again from scratch. ;-) Still, I gather that's not the point of this particular exercise. Since you're interested in comparisons... A method is simply a way of giving the same name to several different functions, and have the compiler pick the correct one based on the argument types. That's what methods do in OOP, and it's what they do in Haskell too. The notable difference is that in Haskell, all types are known at compile-time. (Unless you turn on certain extra non-standard language features...) The other point worth realising is that since Haskell has first-class functions, you don't "need" classes quite so much. (E.g., Java has the Runnable interface so that the JVM can call an object's run() method. In Haskell, you just say forkIO and pass it the function to execute. Similar deal for GUI callbacks and so forth.)

2010/7/25 Andrew Coppin
Patrick Browne wrote:
Andrew, Thanks for your detailed feedback, it is a great help.
Well, I like to be helpful.
I appreciate that the code does not do anything useful, nor is it an appropriate way to write Haskell, but it does help me understand language constructs.
Personally, I find it easier to understand things when they do something meaningful, but sure.
I am studying the Haskell type class system as part of a language comparison. I am trying to exercise and understand the constructs rather than develop a meaningful application.
The best way to understand Haskell is... to completely forget everything you already know, and start again from scratch. ;-) Still, I gather that's not the point of this particular exercise.
Since you're interested in comparisons... A method is simply a way of giving the same name to several different functions, and have the compiler pick the correct one based on the argument types. [snip]
Actually in Haskell, the choice of the correct definition is not only based on the argument types. It could be based on the result type: class C a where f :: a g :: a -> Int h :: String -> a An example of the 'h' case is simply the 'read' function: Prelude> :t read read :: (Read a) => String -> a For instance: Prelude> read "1" :: Int 1 Prelude> read "1" :: Double 1.0 Note that usually, the type annotation is not needed because the compiler has enough information from the context to infer it. Cheers, Thu

Vo Minh Thu wrote:
2010/7/25 Andrew Coppin
: Since you're interested in comparisons... A method is simply a way of giving the same name to several different functions, and have the compiler pick the correct one based on the argument types. [snip]
Actually in Haskell, the choice of the correct definition is not only based on the argument types. It could be based on the result type:
Yes, quite right. It's also possible to use "phantom types" to make the program do different things even thought the run-time representation of data hasn't changed at all. Haskell is like that. ;-)
participants (4)
-
Andrew Coppin
-
Patrick Browne
-
Stephen Tetley
-
Vo Minh Thu