Class or parameterized type?

oleg@pobox.com oleg@pobox.com
Tue, 18 Mar 2003 18:42:09 -0800 (PST)


Hello!

> Example: I wish to define a structured container type, let's call it a 
> "RatsNest", that is type-variable in two ways:

> (a) it is parameterized by a type of some class, let's call it "RatsTail", 
> such that a RatsNest is a structure of things that have common 
> properties.  Certain operations between RatsNest values (e.g. a merge) are 
> valid only if they are containers for the same kind of RatsTail.  Such 
> operations would not be different operations due to variation of thye 
> contained type.

> (b) it can be implemented in various ways;  e.g. a simple version is an 
> in-memory data structure, while another may be implemented in database 
> storage.  This corresponds to the Haskell idea of overloading, or classes.

Do you consider the standard design lacking? For example,

-- sort of things to put into a RatNest
class (Eq n) => 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]

Haskell extensions are required, of course, because we use
multi-parameter type classes.