Dear Steve, et al.,

On 6 Jan 2012, at 11:00, <haskell-cafe-requ...@haskell.org>
 <haskell-cafe-requ...@haskell.org> wrote:

> From: Steve Horne <sh006d3...@blueyonder.co.uk>
> Date: 6 January 2012 10:51:58 GMT
> To: Steffen Schuldenzucker <sschuldenzuc...@uni-bonn.de>
> Cc: Haskell Cafe Mailing List <haskell-cafe@haskell.org>
> Subject: Re: [Haskell-cafe] Simple type-class experiment turns out not so 
> simple...
> 
> 
> On 06/01/2012 10:29, Steffen Schuldenzucker wrote:
>> 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 think what Steffen was saying here is that the only implementation of wbtData 
that satisfies the general type "forall d. n -> Maybe d" is "const Nothing" 
which has precisely that static type (the forall doesn't make it a dynamic 
type).

> 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.

This isn't a general truth, but if you're still in early stages of learning 
about GHCs type-class implementation, you're probably right.

> 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.

The problem with the "forall d. n -> Maybe d" type is that it makes d too 
general (universal, in fact), while d is fixed by n. There is an alternative 
extension you may want to look into for your furtherance of the capabilities of 
GHC, being TypeFamilies. These would lead to the following alternative 
implementation:

{-# LANGUAGE TypeFamilies #-}

class WalkableBinTree n where
  type ElemTp n
  wbtChildren :: n -> Maybe (n, n)
  wbtData     :: n -> Maybe (ElemTp n)

instance WalkableBinTree (BT x) where
  type ElemTp (BT x) = x

  wbtChildren (Branch d l r) = Just (l, r)
  wbtChildren  Empty         = Nothing

  wbtData     (Branch d l r) = Just d
  wbtData      Empty         = Nothing


This says that the instance fixes the "element type" ElemTp to something 
specific. However, it seems perfectly reasonable for the goal you describe to 
demand that whatever tree-type this class is instantiated for must be 
parametric in its element type. This can be done without any language 
extension, i.e.:

class WalkableBinTree n where
  wbtChildren :: n d -> Maybe (n d, n d)
  wbtData     :: n d -> Maybe d

instance WalkableBinTree BT where
  wbtChildren (Branch d l r) = Just (l, r)
  wbtChildren  Empty         = Nothing

  wbtData     (Branch d l r) = Just d
  wbtData      Empty         = Nothing

Notice that now, the class is instantiated for "BT" and *not* "(BT x)".

> 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.

A good way to learn a lot about type classes is to study the default library. 
Admittedly, this can be a bit of a daunting task to just dive in. Luckily, 
Brent Yorgey wrote up a nice article that was transferred and updated by 
numerous people on the HaskellWiki. It's worth giving it a read:

http://www.haskell.org/haskellwiki/Typeclassopedia

Happy Haskelling!

Regards,
Philip

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

Reply via email to