
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