[Haskell-cafe] (no subject)

Matthew Brecknell haskell at brecknell.org
Tue Mar 27 22:19:11 EDT 2007


I'm attempting to construct an abstract data type with a generalised
(deferred) representation. For a simple motivating example, say I am
building an abstract data type with this representation:

> newtype Foo1 k e = Foo1 (Data.Map.Map k (Data.Set.Set e))

While this is a fine default representation, I would like to be able to
substitute IntMap for Map or IntSet for Set in cases where k or e happen
to be Int, or simple list-based map and set implementations for types
lacking an Ord instance.

Following is a prototype of the approach I've come up with so far. It's
been quite an adventure just getting this to type-check (due to lack of
experience with MPTCs and FDs), so I'd be grateful for comments on
whether it is likely to withstand use in real programs, other ways to
solve the problem, etc.

> {-# LANGUAGE FunctionalDependencies #-}
> 
> -- Map class, with generic newtype wrapper instance.
> 
> class MapLike k v m | m -> k v where
>   emptyM :: m
>   insertWithM :: (v -> v -> v) -> k -> v -> m -> m
>   toListM :: m -> [(k,v)]
> 
> newtype Map m k v = Map m
> 
> instance MapLike k v m => MapLike k v (Map m k v) where
>   emptyM = Map emptyM
>   insertWithM f k v (Map m) = Map (insertWithM f k v m)
>   toListM (Map m) = toListM m
> 
> -- Set class, with generic newtype wrapper instance.
> 
> class SetLike e s | s -> e where
>   singletonS :: e -> s
>   unionWithS :: (e -> e -> e) -> s -> s -> s
>   toListS :: s -> [e]
> 
> newtype Set s e = Set s
> 
> instance SetLike e s => SetLike e (Set s e) where
>   singletonS e = Set (singletonS e)
>   unionWithS f (Set s1) (Set s2) = Set (unionWithS f s1 s2)
>   toListS (Set s) = toListS s
> 
> -- Abstract datatype Foo, whose representation is deferred
> -- through the Map and Set newtype wrappers.
> 
> newtype Foo m k s e = Foo (Map m k (Set s e))
> 
> class FooLike k e s m | m -> k s, s -> e where
>   emptyF :: m
>   insertWithF :: (e -> e -> e) -> k -> e -> m -> m
>   toListF :: m -> [(k,e)]
> 
> instance (MapLike k (Set s e) m, SetLike e s) => FooLike k e (Set s e) (Foo m k s e) where
>   emptyF = Foo emptyM
>   insertWithF f k e (Foo m) = Foo (insertWithM (unionWithS f) k (singletonS e) m)
>   toListF (Foo m) = [ (k,e) | (k,s) <- toListM m, e <- toListS s ]

Note that the FooLike class is not strictly necessary to the approach,
since its methods could be written as top-level functions, but I thought
it couldn't hurt. It does have the advantages of consolidating class
constraints in one place, making functional dependencies explicit, and
supporting further composition using the same technique.



More information about the Haskell-Cafe mailing list