a nice Pair,, was: Multiparameter classes in HUGS and GHC
Lloyd Allison
lloyd@mail.csse.monash.edu.au
Fri, 2 May 2003 11:24:16 +1000
On Wed, Apr 30, 2003 at 07:20:06PM +0100, Graham Klyne wrote:
> I've trying to understand better how to use multiparameter classes, and in
> particular the things that can be declared as instances. I've consulted
> the following:
> ...
> [[
> class (Eq k, Show k) => Pair a k v where
> newPair :: (k,v) -> a k v
> getPair :: a k v -> (k,v)
>
> newtype MyPair1 k v = P1 (Int,String)
>
> instance Pair MyPair1 Int String where
> newPair (x,y) = P1 (x,y)
> getPair (P1 (x,y)) = (x,y)
> ...
--The nicest Pair that I've ever managed is not:
class Pair p a b where -- if we use fst' then b is "loose" and v.v.
fst' :: p->a -- seems to be :: forall a.(p->a), regardless class Pair p.
snd' :: p->b -- can't seem to get a and b from the instances.
-- Seems to be a problem overloading both fst and snd in one class
-- but OK if one operator per class ...
--But rather:
-- ... so we can split Pair into two classes, "left" and "right"!
class PairL p a where fst'' :: p->a -- OK but a needs to be implied by use
class PairR p b where snd'' :: p->b -- ditto
instance PairL (((,) a b)) a where fst'' (x,y) = x
instance PairR (((,) a b)) b where snd'' (x,y) = y
-- could make (a trivial) Pair' a subclass of PairL and PairR
--which incidentally will combine with
class Function fnType t u where ($) :: fnType -> t -> u -- NB hid std $
instance Function (t->u) t u where f $ x = f x -- Hask' list 29 Oct 2002
--allowing
instance Function ((t->u),(v->w)) (t,v) (u,w) where
(f, g) $ (x, y) = (f x, g y)
--e.g.
f2b = ( (\ch->if ch=='a' then 'z' else ch), (not) )
... ( (f2b $ ('a', False)) :: (Char,Bool) ) -- need the type
...
Lloyd
--
Lloyd ALLISON, CSSE, Monash University, Victoria, Australia 3800.
web: http://www.csse.monash.edu.au/~lloyd/ tel: +61 3 9905 5205
use: http://www.linux.org/ OpenOffice: http://www.openoffice.org/