
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?