Thanks again for your help with the previous question.  I have another
one.  (If there is a more appropriate forum for simple questions like
this, please let me know; I don't want to waste your time.)

I am confused about the rules for constraints on polymorphic classes.
Suppose I write a class intended to represent a "Map" data structure such
as Java's java.util.Map or Ocaml's Hashtbl.t:

class Map m where
  map_get    :: (Eq a) => m a b -> a -> Maybe b
  map_put    :: (Eq a) => a -> b -> m a b -> m a b
  map_assocs :: (Eq a) => m a b -> [(a, b)]

Say I want to write a binary-tree implementation, which will require the
key type a to have an ordering:

data (Ord a) => BtreeMap a b =
  Leaf | Branch a b (BtreeMap a b) (BtreeMap a b)
  deriving (Eq, Ord, Show)
instance Map BtreeMap where -- this doesn't work
-- (obvious implementations)

Then BtreeMap is not an instance of Map, because its methods come with the
constraint (Ord a).  If I instead write the class

class SortedMap m where
  map_get    :: (Ord a) => m a b -> a -> Maybe b
  map_put    :: (Ord a) => a -> b -> m a b -> m a b
  map_assocs :: (Ord a) => m a b -> [(a, b)]

then the instance declaration
instance SortedMap BtreeMap where
-- (obvious declarations)

works fine.  But with this setup, every Map is a SortedMap, because the
constraint on the key type is looser for Map.  This is the opposite of
what I want!

I think I just haven't understood the Haskell Way to do this.  Can you
show me what I'm missing?

A related question -- Suppose instead I want to implement Map with
association lists:
type Alist a b = [(a, b)]
instance Map Alist where -- this doesn't work
  map_get [] x' = Nothing
  map_get ((x, y):pairs) x' | x' == x   = Just y
                            | otherwise = map_get pairs x'
  map_put x' y' [] = [(x', y')]
  map_put x' y' ((x, y):pairs) | x' == x   = (x, y'):pairs
                               | otherwise = (x, y):(map_put x' y' pairs)     
  map_assocs m = m

This doesn't work because the type synonym Alist cannot be partially
applied, being a type synonym.  But if I use `newtype' instead, then I
have to clutter up the code with an identity type constructor `A' and
projector `unA'.  Is there a cleaner way to do it?

thanks & peace,
Chris Jeris




Reply via email to