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.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to