
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.

Yesterday, I wrote an email with no subject header:
I'm attempting to construct an abstract data type with a deferred representation. [...]
I got rid of those annoying Map and Set newtype wrappers from my previous post, after realising that the only reason I had needed them was to eliminate a coverage condition failure on a FooLike class parameter that wasn't rightfully part of the FooLike abstraction. Having eliminated that thinko, it all seems rather obvious now (revised code follows). It's been said that the type system is good at telling you when you've done something wrong, but this is the first time I've seen it give strong hints that something is unnecessarily overcomplicated even though it does work.
{-# LANGUAGE FunctionalDependencies #-}
import qualified Data.IntMap as IM import qualified Data.IntSet as IS import qualified Data.Map as M import qualified Data.Set as S
-- MapLike and SetLike classes, used as the basis for the -- implementation of the Foo abstract datatype.
class MapLike k v m | m -> k v where emptyM :: m insertWithM :: (v -> v -> v) -> k -> v -> m -> m toListM :: m -> [(k,v)]
class SetLike e s | s -> e where singletonS :: e -> s unionS :: s -> s -> s toListS :: s -> [e]
-- Implementation of Foo abstract datatype as simple top-level functions. -- No need for a concrete type at this point.
tl_emptyF :: (MapLike k s m, SetLike e s) => m tl_emptyF = emptyM
tl_insertF :: (MapLike k s m, SetLike e s) => k -> e -> m -> m tl_insertF k e m = insertWithM unionS k (singletonS e) m
tl_toListF :: (MapLike k s m, SetLike e s) => m -> [(k,e)] tl_toListF m = [ (k,e) | (k,s) <- toListM m, e <- toListS s ]
-- FooLike class API for Foo abstract datatype.
class FooLike k e f | f -> k e where emptyF :: f insertF :: k -> e -> f -> f toListF :: f -> [(k,e)]
-- Generic FooLike instance, constructed in terms of MapLike and SetLike. -- Details of the concrete type are deferred.
newtype Foo k e s m = Foo m
instance (MapLike k s m, SetLike e s) => FooLike k e (Foo k e s m) where emptyF = Foo tl_emptyF insertF k e (Foo m) = Foo (tl_insertF k e m) toListF (Foo m) = tl_toListF m
-- Some MapLike and SetLike instances, for the tests that follow.
instance Ord k => MapLike k v (M.Map k v) where emptyM = M.empty insertWithM = M.insertWith toListM = M.toList
instance MapLike Int v (IM.IntMap v) where emptyM = IM.empty insertWithM = IM.insertWith toListM = IM.toList
instance Ord e => SetLike e (S.Set e) where singletonS = S.singleton unionS = S.union toListS = S.toList
instance SetLike Int IS.IntSet where singletonS = IS.singleton unionS = IS.union toListS = IS.toList
-- Some simple tests.
type FooOrdOrd k e = Foo k e (S.Set e) (M.Map k (S.Set e)) type FooIntOrd e = Foo Int e (S.Set e) (IM.IntMap (S.Set e)) type FooOrdInt k = Foo k Int IS.IntSet (M.Map k IS.IntSet) type FooIntInt = Foo Int Int IS.IntSet (IM.IntMap IS.IntSet)
testFoo t = toListF $ insertF 3 2 $ insertF 5 1 $ insertF 3 2 $ insertF 5 2 $ asTypeOf emptyF t
main = do print $ testFoo (undefined :: FooOrdOrd Integer Integer) print $ testFoo (undefined :: FooIntOrd Integer) print $ testFoo (undefined :: FooOrdInt Integer) print $ testFoo (undefined :: FooIntInt)
participants (1)
-
Matthew Brecknell