Re: [Haskell-beginners] Typeclasses vs. Data

Hello David! Yes, I should have posted the signatures, too. Sorry. I managed to simplify the problem even further. It still doesn't help me understand how to avoid the error, though. class Continuation a where resume :: a -> Int -> Int data BeginCont a = BeginCont a Int deriving (Show) instance (Continuation a) => Continuation (BeginCont a) where resume (BeginCont k es) v = eval_begin es k eval :: Continuation a => Int -> a -> Int eval n k = if n < 1 then resume k n else eval_begin (n - 1) k eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = eval n (if (n < 0) then k else (BeginCont k (n - 1))) It's pretty clear that in the mutual recursion between "eval" and "eval_begin" the parameter "k" is "growing" from "a" to "BeginCont a" and so on. But how to resolve that? (And it works perfectly in the case of the "data" definition.) Anyway, thank you! Regards, Thomas On 21.07.2011 00:40, David Place wrote:
On Jul 20, 2011, at 6:26 PM, Thomas wrote:
Thank you for taking the time. Here is a complete fragment that shows the error:
Hi, Thomas.
I'm very sympathetic. I hate it when I get an error like this. I looked at your code and the solution didn't jump off the page, maybe it will for someone else. In the meantime, I suggest this strategy. Carefully give type signatures to all of your functions. This way you can help the type checker give better error messages. The type inference algorithm can go away into crazy land if you give it a nonsense definition.
___________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

On Jul 20, 2011, at 7:41 PM, Thomas wrote:
It's pretty clear that in the mutual recursion between "eval" and "eval_begin" the parameter "k" is "growing" from "a" to "BeginCont a" and so on. But how to resolve that?
Progress, though? You're getting a different error message.
Couldn't match type `a' with `BeginCont a' `a' is a rigid type variable bound by the type signature for eval_begin :: Continuation a => Int -> a -> Int at ../Desktop/devl/hs/TryPQ.hs:16:1 In the return type of a call of `BeginCont' In the expression: (BeginCont k (n - 1)) In the second argument of `eval', namely `(if (n < 0) then k else (BeginCont k (n - 1)))'

On Wed, Jul 20, 2011 at 8:41 PM, Thomas
eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = eval n (if (n < 0) then k else (BeginCont k (n - 1)))
Although 'eval n' is polymorphic, the if expression needs to have just one type, either 'a' or 'BeginCont a', and they can't be unified. The solution is pretty simple, though, since eval's return type doesn't mention 'a' at all: eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = if (n < 0) then eval n k else eval n (BeginCont k (n - 1)) Note that 'eval n' is repeated. If you don't to repeat it on your real world code you may give it an explicit name. However you'll need to provide a type signature from GHC 7.0 onwards: eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = let eval' :: Continuation a => a -> Int eval' = eval n in if (n < 0) then eval' k else eval' (BeginCont k (n - 1)) HTH, =) -- Felipe.

Hi Felipe, David! It works!!! :-) What I do not really understand, however, is the difference between eval_begin n k = eval n (if (n< 0) then k else (BeginCont k (n - 1))) and eval_begin n k = if (n< 0) then eval n k else eval n (BeginCont k (n - 1)) Anyway, it works and since I needed to use the "Rank2Types" and "RelaxedPolyRec" extensions I have to read (and hopefully understand ;-) these as well. Maybe they'll shed some light onto this. I just wonder: Are typeclasses such an advanced feature that I'd better use alternatives wherever possible? Yitzchak suggested this in this list a few days ago. But almost every (introductory) text explains them as a basic feature. Thanks a lot to both of you! Thomas On 21.07.2011 05:27, Felipe Almeida Lessa wrote:
On Wed, Jul 20, 2011 at 8:41 PM, Thomas
wrote: eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = eval n (if (n< 0) then k else (BeginCont k (n - 1)))
Although 'eval n' is polymorphic, the if expression needs to have just one type, either 'a' or 'BeginCont a', and they can't be unified. The solution is pretty simple, though, since eval's return type doesn't mention 'a' at all:
eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = if (n< 0) then eval n k else eval n (BeginCont k (n - 1))
Note that 'eval n' is repeated. If you don't to repeat it on your real world code you may give it an explicit name. However you'll need to provide a type signature from GHC 7.0 onwards:
eval_begin :: Continuation a => Int -> a -> Int eval_begin n k = let eval' :: Continuation a => a -> Int eval' = eval n in if (n< 0) then eval' k else eval' (BeginCont k (n - 1))
HTH, =)

On Jul 21, 2011 5:28 AM, "Thomas"
Hi Felipe, David!
It works!!! :-)
What I do not really understand, however, is the difference between
eval_begin n k = eval n (if (n< 0) then k else (BeginCont k (n - 1))) and
eval_begin n k = if (n< 0) then eval n k else eval n (BeginCont k (n -
1))
The difference comes down to two things: 1. The type of 'if'. The haskell 'if ... then ... else ...' is conceptually just a function with the type (Bool -> a -> a -> a). The two branches must be of the same type. 2. In the code:
f (if p then a else b)
If somehow the 'if' could type-check with 'a' and 'b' being of different types, the compiler wouldn't know which type to pick for 'f'. In Haskell, we're not allowed to delay type-checking until run-time - the compiler demands that it can solve everything before running any of it. I hope I haven't confused things even more! Antoine

Hello Antoine! Thank you for the explanation. I think I get closer with it. So my understanding is this: In my example both 'a' and 'b' were of the same typeclass. In fact they were of the same type, too, since in the example the class had only one instance. However, the compiler/type checker could not prove this to be true. But if this was the case then I should be able to convince the compiler via type annotations like if p then (a :: (MyTC a) => a) else (b :: (MyTC a) => a) which does not work ('Inferred type is less polymorphic then expected.') Probably I do not yet understand well the relationship between types and type classes... Regards, Thomas On 21.07.2011 14:04, Antoine Latter wrote: [...]
The difference comes down to two things:
1. The type of 'if'. The haskell 'if ... then ... else ...' is conceptually just a function with the type (Bool -> a -> a -> a). The two branches must be of the same type.
2. In the code:
f (if p then a else b)
If somehow the 'if' could type-check with 'a' and 'b' being of different types, the compiler wouldn't know which type to pick for 'f'. In Haskell, we're not allowed to delay type-checking until run-time - the compiler demands that it can solve everything before running any of it.
I hope I haven't confused things even more!
Antoine

On Thu, Jul 21, 2011 at 9:58 AM, Thomas
So my understanding is this: In my example both 'a' and 'b' were of the same typeclass. In fact they were of the same type, too, since in the example the class had only one instance. However, the compiler/type checker could not prove this to be true.
Actually they had different types and the compiler could see it :). Let's see that if again: if n < 0 then k else BeginCont k (n - 1) Let's say that 'k' has type X. What is the type of 'BeginCont k (n - 1)'? Well, we have data BeginCont a = BeginCont a Int so given that the first parameter of the 'BeginCont' is 'k', which has type 'X', then 'BeginCont k (n-1)' has type 'BeginCont X'. So this is what we have: if n < 0 then (k :: X) else (BeginCont k (n-1) :: BeginCont X) What is the type of the whole 'if'? It must be the unification of 'X' and 'BeginCont X'. But we can't unify these types. It doesn't really matter that both 'X' and 'BeginCont X' are instances of some typeclass MyTC, and that the function that will take the result of the 'if' just needs the typeclass and nothing else. We can't typecheck the 'if'.
But if this was the case then I should be able to convince the compiler via type annotations like if p then (a :: (MyTC a) => a) else (b :: (MyTC a) => a) which does not work ('Inferred type is less polymorphic then expected.')
It is less polymorphic because 'k' has a rigid, defined type. Its type was chosen by the one who called the function. He gave you some 'k' that satisfy the class constraint, but you don't know which one. HTH, =) -- Felipe.

On Jul 21, 2011, at 9:09 AM, Felipe Almeida Lessa wrote:
It is less polymorphic because 'k' has a rigid, defined type. Its type was chosen by the one who called the function. He gave you some 'k' that satisfy the class constraint, but you don't know which one.
I think that Thomas made an interesting step in his first post that may explain the problem. First, he created a type that had (or would eventually have had) constructors for each of the different kinds of continuations. This type is proper type in the mind of the type inference algorithm. Then, in the interest of modularity, he substituted a class for the type. The class is not a proper type, so the substitution doesn't work. I remember going through this same confusion coming from a more object-oriented way of thinking. A class in Haskell is more like an interface or a protocol in object-oriented languages. I think of it as an orthogonal construct to type. ____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

Hello! I think the pieces all start to fall into place. :-) I still haven't truly understood typeclasses, but at least I see progress in my understanding. The analogy between OO-interfaces and typeclasses seems to be a bit misleading here, though. Because IIUC then in Haskell typeclasses are not a substitute for a type - a misconception that bit me here, while in (at least the OO-languages I use) interfaces can usually be used instead of types (except object creation & assignment). For example: if n < 0 then (k :: X) else (BeginCont k (n-1) :: BeginCont X) does not type check in Haskell. The "equivalent" construct would type check in OO(*) - although I understand that this does not mean the same in OO as in Haskell. Probably type classes are really orthogonal to types as David writes. But then I would consider them as rather different from interfaces in OO, too. Well, the Haskell road is still long for me, but it's real fun travelling... ;-) Thank you, everybody! Thomas PS: *) class BeginCont : public InterfaceX ... if(n < 0) { k; // type is: InterfaceX* } else { new BeginCont(k, (n - 1)); // type is: BeginCont* ~= InterfaceX* } Ok, the type check is trivial (essentially a NOOP) in the code above, but it would even type check as: CallWithInterfaceX((n<0)?k:new BeginCont(k, n-1)); which is rather close to the Haskell code semantically. On 21.07.2011 15:24, David Place wrote:
On Jul 21, 2011, at 9:09 AM, Felipe Almeida Lessa wrote:
It is less polymorphic because 'k' has a rigid, defined type. Its type was chosen by the one who called the function. He gave you some 'k' that satisfy the class constraint, but you don't know which one.
I think that Thomas made an interesting step in his first post that may explain the problem. First, he created a type that had (or would eventually have had) constructors for each of the different kinds of continuations. This type is proper type in the mind of the type inference algorithm. Then, in the interest of modularity, he substituted a class for the type. The class is not a proper type, so the substitution doesn't work.
I remember going through this same confusion coming from a more object-oriented way of thinking. A class in Haskell is more like an interface or a protocol in object-oriented languages. I think of it as an orthogonal construct to type.
____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

On Thu, Jul 21, 2011 at 12:22 PM, Thomas
The analogy between OO-interfaces and typeclasses seems to be a bit misleading here, though. Because IIUC then in Haskell typeclasses are not a substitute for a type - a misconception that bit me here, while in (at least the OO-languages I use) interfaces can usually be used instead of types (except object creation & assignment).
I prefer to say that the only similarity between OO classes and typeclasses is the word "class". Trying to make comparisons always ends in tears.
For example: if n < 0 then (k :: X) else (BeginCont k (n-1) :: BeginCont X) does not type check in Haskell. The "equivalent" construct would type check in OO(*) - although I understand that this does not mean the same in OO as in Haskell.
It is possible to do the same in Haskell using existentials. But forget that I've said that and don't try to use it. Most of the time you don't need them and there are better solutions. Cheers, =) -- Felipe.

On Thu, Jul 21, 2011 at 12:26:15PM +0200, Thomas wrote:
I just wonder: Are typeclasses such an advanced feature that I'd better use alternatives wherever possible?
No. Typeclasses are a (relatively) straightforward, and quite useful, feature. Yitzchak was arguing that type classes are often overused by beginners, for purposes where other, better solutions exist. If you find yourself using type classes all over the place for everything then perhaps you are using them too much. But there is no need to avoid them completely, and certainly not because they are "too advanced". The obvious question you may be wondering is "well, when should I use them and when shouldn't I?" Unfortunately I can't answer that off the top of my head. Just read and write a lot of code, try out different ways of solving problems, and you'll start to get a feel for what works well and what doesn't. -Brent
participants (5)
-
Antoine Latter
-
Brent Yorgey
-
David Place
-
Felipe Almeida Lessa
-
Thomas