Type classes confusion

andrew cooke andrew at acooke.org
Sat Jan 10 18:07:50 EST 2004


Hi,

I'm trying to use type classes and suspect I've got confused somewhere
down the line, because I've got to an error message that I don't
understand and can't remove.

I have a class that works like a hash table, mapping from String to some
type.  I have two instances, one that is case insensitive for keys.  I
want to hide these instances from the rest of the code, which should only
use the class.  This class is called Dictionary.

In addition, for Dictionaries that map Strings to Strings, I have some
functions which do substitutions on Strings using their own contents. 
Possibly the first source of problems is that I can't find a way to
express these two classes together without multiple parameter type classes
(one parameter for the case/no case and one for the type returned):

class Dictionary d a where
  add'       :: d a -> (String, a) -> d a
  ...

instance Dictionary DictNoCase a where
  add' d (k, v) = ...

-- Dict is the underlying tree implementation and Maybe stores the
-- value for the null (empty string) key.
data DictNoCase a = DictNoCase (Dict a) (Maybe a)

class (Dictionary d String) => SubDictionary d where
  substitute :: d String -> String -> String
  ...

instance SubDictionary DictNoCase where
  substitute d s = ...

All the above compiles and seems correct (is it?).

I also provide an empty instance of the two instance types.  For
DictNoCase, this is
empty = DictCase Empty Nothing
where Empty is the empty type constructor for Dict

Now (almost there) elsewhere I want to define a data type that contains
two of these Dictionaries.  One stores String values.  The other stores
functions that take this same type and return a result and a copy of the
type:

data Context s f = (Dictionary s String, Dictionary f (CustomFn s f)) =>
    Ctx {state :: s String,
         funcs :: f (CustomFn s f)}

type CustomFn s f = Context s f -> Arg -> IO (Context s f, Result s f)

data Result s f = Attr Name String
                | Repeat (CustomFn s f)
                ...

newContext = Ctx empty emptyNC

(where empty is the case-sensitive empty dictionary)

Now THAT doesn't compile:

Template.lhs:60:
    All of the type variables in the constraint `Dictionary s
                                                            String' are
already
in scope
        (at least one must be universally quantified here)
    When checking the existential context of constructor `Ctx'
    In the data type declaration for `Context'

Template.lhs:60:
    All of the type variables in the constraint `Dictionary f
                                                            (CustomFn s
f)' are
already in scope
        (at least one must be universally quantified here)
    When checking the existential context of constructor `Ctx'
    In the data type declaration for `Context'

where line 60 is "data Context...."

And I can't see what I've done wrong.  Any help gratefully received.

Cheers,
Andrew

-- 
personal web site: http://www.acooke.org/andrew
personal mail list: http://www.acooke.org/andrew/compute.html


More information about the Haskell mailing list