Simple type-class experiment turns out not so simple...

I was messing around with type-classes (familiarization exercises) when I hit a probably newbie problem. Reducing it to the simplest case... module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where -- n : node type -- d : data item type wrapped in each node class WalkableBinTree n where wbtChildren :: n -> Maybe (n, n) wbtData :: n -> Maybe d -- Simple tree type, mostly for testing data BT x = Branch x (BT x) (BT x) | Empty instance WalkableBinTree (BT x) where wbtChildren (Branch d l r) = Just (l, r) wbtChildren Empty = Nothing wbtData (Branch d l r) = Just d wbtData Empty = Nothing Loading this code into GHCi, I get... Prelude> :load BinTree [1 of 1] Compiling BinTree ( BinTree.hs, interpreted ) BinTree.hs:16:39: Couldn't match type `x' with `d' `x' is a rigid type variable bound by the instance declaration at BinTree.hs:12:32 `d' is a rigid type variable bound by the type signature for wbtData :: BT x -> Maybe d at BinTree.hs:16:5 In the first argument of `Just', namely `d' In the expression: Just d In an equation for `wbtData': wbtData (Branch d l r) = Just d Failed, modules loaded: none. Prelude> I've tried varying a number of details. Adding another parameter to the type-class (for the item-data type) requires an extension, and even then the instance is rejected because (I think) the tree-node and item-data types aren't independent. In any case, I can't understand why those types can't match.

On 01/06/2012 11:16 AM, Steve Horne wrote:
I was messing around with type-classes (familiarization exercises) when I hit a probably newbie problem. Reducing it to the simplest case...
module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where -- n : node type -- d : data item type wrapped in each node class WalkableBinTree n where wbtChildren :: n -> Maybe (n, n) wbtData :: n -> Maybe d
With 'd' not being mentioned anywhere, the signature of wbtData means "forall d. n -> Maybe d". In particular, wbtData == const Nothing.
-- Simple tree type, mostly for testing data BT x = Branch x (BT x) (BT x) | Empty
instance WalkableBinTree (BT x) where wbtChildren (Branch d l r) = Just (l, r) wbtChildren Empty = Nothing
wbtData (Branch d l r) = Just d wbtData Empty = Nothing
The signature of this function is 'BT x -> Maybe x', so it doesn't match the one above.
Loading this code into GHCi, I get...
Prelude> :load BinTree [1 of 1] Compiling BinTree ( BinTree.hs, interpreted )
BinTree.hs:16:39: Couldn't match type `x' with `d' `x' is a rigid type variable bound by the instance declaration at BinTree.hs:12:32 `d' is a rigid type variable bound by the type signature for wbtData :: BT x -> Maybe d at BinTree.hs:16:5 In the first argument of `Just', namely `d' In the expression: Just d In an equation for `wbtData': wbtData (Branch d l r) = Just d Failed, modules loaded: none. Prelude>
...which this error message tells you.
I've tried varying a number of details. Adding another parameter to the type-class (for the item-data type) requires an extension, and even then the instance is rejected because (I think) the tree-node and item-data types aren't independent.
Did you try something like
{-# LANGUAGE MultiParamTypeClasses #-} class WalkableBinTree n d where ... (same code as above, but 'd' is bound now) ... instance WalkableBinTree (BT x) x where ...
-- Steffen

On 06/01/2012 10:29, Steffen Schuldenzucker wrote:
On 01/06/2012 11:16 AM, Steve Horne wrote:
I was messing around with type-classes (familiarization exercises) when I hit a probably newbie problem. Reducing it to the simplest case...
module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where -- n : node type -- d : data item type wrapped in each node class WalkableBinTree n where wbtChildren :: n -> Maybe (n, n) wbtData :: n -> Maybe d
With 'd' not being mentioned anywhere, the signature of wbtData means "forall d. n -> Maybe d". In particular, wbtData == const Nothing.
I'm not sure what to make of that. Even if the result of wbtData is always Nothing, surely it still has a static type?
I've tried varying a number of details. Adding another parameter to the type-class (for the item-data type) requires an extension, and even then the instance is rejected because (I think) the tree-node and item-data types aren't independent.
Did you try something like
{-# LANGUAGE MultiParamTypeClasses #-} class WalkableBinTree n d where ... (same code as above, but 'd' is bound now) ... instance WalkableBinTree (BT x) x where ...
Precisely that. In that case, I get... C:\_SVN\dev_trunk\haskell\examples>ghci -XMultiParamTypeClasses GHCi, version 7.0.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> :load BinTree [1 of 1] Compiling BinTree ( BinTree.hs, interpreted ) BinTree.hs:12:12: Illegal instance declaration for `WalkableBinTree (BT x) x' (All instance types must be of the form (T a1 ... an) where a1 ... an are *distinct type variables*, and each type variable appears at most once in the instance head. Use -XFlexibleInstances if you want to disable this.) In the instance declaration for `WalkableBinTree (BT x) x' Failed, modules loaded: none. Prelude> If I specify both extensions (-XMultiParamTypeClasses and -XFlexibleInstances) it seems to work, but needing two language extensions is a pretty strong hint that I'm doing it the wrong way. The goal is fairly obvious - to have type-classes for binary tree capabilities so that different implementations can support different subsets of those capabilities. Being able to walk a binary tree doesn't need ordering of keys, whereas searching does. A red-black tree needs somewhere to store it's colour in the node, yet the walking and searching functions don't need to know about that. As far as I remember, none of the tutorials I've read have done this kind of thing - but it seemed an obvious thing to do. Obviously in the real world I should just use library containers, but this is about learning Haskell better in case a similar problem arises that isn't about binary trees. How should I be handling this?

On 01/06/2012 11:51 AM, Steve Horne wrote:
On 06/01/2012 10:29, Steffen Schuldenzucker wrote:
On 01/06/2012 11:16 AM, Steve Horne wrote:
[...]
module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where -- n : node type -- d : data item type wrapped in each node class WalkableBinTree n where wbtChildren :: n -> Maybe (n, n) wbtData :: n -> Maybe d
[...]
Did you try something like
{-# LANGUAGE MultiParamTypeClasses #-} class WalkableBinTree n d where ... (same code as above, but 'd' is bound now) ... instance WalkableBinTree (BT x) x where ...
[...]
If I specify both extensions (-XMultiParamTypeClasses and -XFlexibleInstances) it seems to work, but needing two language extensions is a pretty strong hint that I'm doing it the wrong way. [...]
Well, if your instances always look like
instance WalkableBinTree (SomeTypeConstructor x) x
you could make WalkableBinTree take a type constructor of kind (* -> *) like this:
class WalkableBinTree t where wbtChildren :: t x -> (t x, t x) wbtData :: t x -> Maybe x instance WalkableBinTree BT where ...
Of course, you loose flexibility compared to the multi param approach, e.g. you couldn't add type class constraints for the element type 'x' in an instance declaration.

On Fri, Jan 06, 2012 at 10:51:58AM +0000, Steve Horne wrote:
If I specify both extensions (-XMultiParamTypeClasses and -XFlexibleInstances) it seems to work, but needing two language extensions is a pretty strong hint that I'm doing it the wrong way.
Not necessarily. These two extensions in particular (and especially the second) are quite uncontroversial. -Brent

On Sun, Jan 8, 2012 at 9:25 PM, Brent Yorgey
On Fri, Jan 06, 2012 at 10:51:58AM +0000, Steve Horne wrote:
If I specify both extensions (-XMultiParamTypeClasses and -XFlexibleInstances) it seems to work, but needing two language extensions is a pretty strong hint that I'm doing it the wrong way.
Not necessarily. These two extensions in particular (and especially the second) are quite uncontroversial.
I really don't know much about the subject, but http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDile... does not sound "uncontroversial" to me. That's why I avoided them so far. - Chris

On Sun, Jan 8, 2012 at 15:55, Christoph Breitkopf < chbreitkopf@googlemail.com> wrote:
On Sun, Jan 8, 2012 at 9:25 PM, Brent Yorgey
wrote: On Fri, Jan 06, 2012 at 10:51:58AM +0000, Steve Horne wrote:
If I specify both extensions (-XMultiParamTypeClasses and -XFlexibleInstances) it seems to work, but needing two language extensions is a pretty strong hint that I'm doing it the wrong way.
Not necessarily. These two extensions in particular (and especially the second) are quite uncontroversial.
http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDile...
does not sound "uncontroversial" to me. That's why I avoided them so far.
MPTCs are not controversial. They're also of limited (but extant) usefulness without an additional extension; and, while there is "controversy" there, it's not especially relevant until type families are stabilized. They could in theory go into the standard *now*; they'd just be of limited use until functional dependencies vs. type families is settled. (Also, de facto I think it's already more or less been decided in favor of type families, just because functional dependencies are (a) a bit alien [being a glob of Prolog-style logic language imported into the middle of System Fc] and (b) [as I understand it] difficult to verify that the code in the compiler is handling all the potential corner cases right [mainly because of (a)]. In any case, if the code in question doesn't happen to need either functional dependencies or type classes, the controversy doesn't touch it. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 08/01/2012 21:13, Brandon Allbery wrote:
(Also, de facto I think it's already more or less been decided in favor of type families, just because functional dependencies are (a) a bit alien [being a glob of Prolog-style logic language imported into the middle of System Fc] and (b) [as I understand it] difficult to verify that the code in the compiler is handling all the potential corner cases right [mainly because of (a)].
Without meaning to express an opinion either way about an issue I don't understand... Isn't Haskell doing some prolog-ish things anyway? I thought the compiler must be doing unification to resolve type inference within expressions. It's not a simple expression evaluation problem (just evaluate the type rather than the value) because sometimes you know the return type but not (yet) the argument types - type information flows bottom-up and top-down through the same expression tree. I could easily be mistaken, though. Looking at the similar overload-resolution problem, Ada can resolve based on return types but C++ cannot. Ada needs unification or something similar to resolve overloading, whereas C++ just evaluates expressions for type instead of value. I can't now say for sure where I picked up the idea that Haskell needs unification to resolve type inference, but I've had some odd error messages which seem to confirm that belief - I assume because the mistake doesn't cause an immediate conflict, instead causing an indirect conflict somewhere else in the larger expression.

Hi, On Mon, Jan 09 2012 at 10:37 +0100, Steve Horne wrote:
On 08/01/2012 21:13, Brandon Allbery wrote:
(Also, de facto I think it's already more or less been decided in favor of type families, just because functional dependencies are (a) a bit alien [being a glob of Prolog-style logic language imported into the middle of System Fc] and (b) [as I understand it] difficult to verify that the code in the compiler is handling all the potential corner cases right [mainly because of (a)].
Isn't Haskell doing some prolog-ish things anyway?
I thought the compiler must be doing unification to resolve type inference within expressions.
Even quite basic type reconstruction (e.g. for ML) needs unification, see e.g. Pierce TaPL chapter 22. The algorithm is rather easy to understand and implement. Based on that, I wouldn't think using /some kind of unification/ in the compilation process qualifies as being particularly prolog-ish. I suppose ``...importing a Prolog-style logic language...'' would mean to allow a significantly more powerful (and explicit) way of expressing constraints in the type system than before. I believe Brandon Allbery, when he says that this is difficult. Best regards Lu

On 1/9/12 7:54 AM, Luminous Fennell wrote:
On Mon, Jan 09 2012 at 10:37 +0100, Steve Horne wrote:
On 08/01/2012 21:13, Brandon Allbery wrote:
(Also, de facto I think it's already more or less been decided in favor of type families, just because functional dependencies are (a) a bit alien [being a glob of Prolog-style logic language imported into the middle of System Fc] and (b) [as I understand it] difficult to verify that the code in the compiler is handling all the potential corner cases right [mainly because of (a)].
Isn't Haskell doing some prolog-ish things anyway?
I thought the compiler must be doing unification to resolve type inference within expressions.
Even quite basic type reconstruction (e.g. for ML) needs unification, see e.g. Pierce TaPL chapter 22. The algorithm is rather easy to understand and implement.
Though it can be somewhat involved to optimize, since the naive implementation is really quite inefficient. If you don't want to worry about the details, there's always: http://hackage.haskell.org/package/unification-fd -- Live well, ~wren

On 08/01/2012 20:25, Brent Yorgey wrote:
If I specify both extensions (-XMultiParamTypeClasses and -XFlexibleInstances) it seems to work, but needing two language extensions is a pretty strong hint that I'm doing it the wrong way. Not necessarily. These two extensions in particular (and especially
On Fri, Jan 06, 2012 at 10:51:58AM +0000, Steve Horne wrote: the second) are quite uncontroversial.
As it turns out, I don't need extensions at all, at least for walkableBinTree. Two answers pointed out how to handle that. I'm not yet entirely sure what will happen when I start adding more typeclasses (searchableBinTree etc) to the family - I've been distracted. Also - after reading those answers and trying the suggestions, I'm pretty sure I've done tutorials that covered this after all. I must have just left it too long before trying them out properly.
participants (7)
-
Brandon Allbery
-
Brent Yorgey
-
Christoph Breitkopf
-
Luminous Fennell
-
Steffen Schuldenzucker
-
Steve Horne
-
wren ng thornton