Class or parameterized type?

oleg@pobox.com oleg@pobox.com
Thu, 20 Mar 2003 11:41:14 -0800 (PST)


Hello!

> I wasn't aware there was a standard design,
Edison is a good standard (in particular, Collection.hs, found, for
example, in /usr/local/share/hugs/lib/exts/).
The following projects have a lot of helpful code:

	http://sourceforge.net/projects/hbase/
	http://sourceforge.net/projects/hfl/

> [[
> class (RatTail t) => RatNest c t where
> ]]

> which I think is exactly what I was looking for, and is not a Haskell 
> structure I've come across before.  (I assume that this form does not 
> indicate that RatNest... is a subclass of RatTail (as opposed to saying 
> (RatTail t) => RatNest t);  I certainly wouldn't want to have that.)

Indeed,
> class (RatTail t) => RatNest c t where

says that collections of a class RatNest have elements of a class
RatTail t: but collections themselves are not in the class
RatTail. Using the OOP slang (which I hate), RatNest has-a RatTail but
RatNest is-not-a RatTail. The method is_the_same_rat applies, in
general, only to the elements of a RatNest, but not to the nest itself.


Nothing prevents us from declaring a particular instance of a RatNest
to be an instance of a RatTail as well. We can then store those
instances in a RatNest.

Nothing prevents us from making any RatNest a RatTail, so we can
always store nests inside nests.

-- sort of things to put into a RatNest
-- Unlike the code in the previous message, 
-- this class declaration does not have the Eq context
class RatTail n where
    is_the_same_rat:: n -> n -> Bool

class (RatTail t) => RatNest c t where
    in_nest:: c t -> t -> Bool
    put:: c t -> t -> c t
    rat_fold:: (t -> z -> z) -> z -> (c t) -> z
    merge:: (RatNest c1 t) => c t -> c1 t -> c t
    merge c c1 = rat_fold put_perhaps c c1
       where put_perhaps rat nest = if in_nest nest rat then nest
	                            else put nest rat

instance RatTail Int where
    is_the_same_rat = (==)

-- Pretend this is an in-memory implementation
instance (RatTail t) => RatNest [] t where
    in_nest lst el = not $ null $ filter (is_the_same_rat el) lst
    put = (flip (:))
    rat_fold = foldr

-- Pretend this is a "disk" implementation
-- At least it's unmarshalled.
newtype Disk t = D String deriving Show

instance (Read t, Show t, RatTail t) => RatNest Disk t where
    in_nest disk el 
            = rat_fold (\item z -> z || is_the_same_rat item el) False disk
    put (D block) item = D $ '|' : ((show item) ++ block)
    rat_fold f z (D []) = z
    rat_fold f z (D ('|':block)) = f item $ rat_fold f z (D rest)
          where  [(item,rest)] = readsPrec 1 block
		
nest1 = [1,12,123] :: [Int]
nest2 = D ""
test1 = merge nest2 nest1 -- D "|1|12|123"
test1' = merge test1 nest1 -- D "|1|12|123"
test2 = merge [4,5,123] test1 -- [1,12,4,5,123]

-- Every RatNest is a RatTail
instance (RatTail t, RatNest c t) => RatTail (c t) where
    is_the_same_rat c1 c2 = subnest c1 c2 && subnest c2 c1
       where subnest c1 c2 
	       = rat_fold (\item res -> in_nest c1 item && res) True c2
	     
-- Now we can make nests of nests
test3 = merge [nest1] [test2] -- [[1,12,4,5,123],[1,12,123]]
test3' = merge [nest1] [nest1] -- [[1,12,123]]
test4 = put nest2 nest1 -- "|[1,12,123]"
test5 = merge test4 (put test4 test2) -- D "|[1,12,4,5,123]|[1,12,123]"
test7 = put [] test5 -- [D "|[1,12,4,5,123]|[1,12,123]"]

The test7 shows three nested nests.

> I suppose this is the multi-parameter type class extension you 
> mentioned.  Can you say where this extension is described, and how widely 
> implemented it is?

GHC (with the flag -fglasgow-exts) and Hugs (with the flag -98)
implement it. I think NHC does too.