Functional dependencies and Constructor Classes

Martin Sulzmann sulzmann@comp.nus.edu.sg
Wed, 20 Nov 2002 17:53:17 +0800 (GMT-8)


Mark P Jones writes:
 > | The issue I want to raise is whether constructor classes are 
 > | redundant in the presence of FDs
 > 
 > No, they are not comparable.
 > 
Allow me to make the following bold claim.

Assume we are given a program that uses the Haskell functor class as in

class Functor f where
   fmap :: (a->b)->(f a->f b)

We translate such a program by using

class Fmap a b fa fb | a fb -> b fa, 
                       b fa -> a fb,
                       fa fb -> a b 
    where fmap :: (a->b)->(fa -> fb) 

instead. Instances are translated in the "obvious" way.
Then, if the original program is typable, so will be the translated
program, meaning is preserved.

 > Your fds version of the Functor class is also incomparable with the
 > ccs version; the former will allow an expression like (map id 'a')

Yes, because FD's are not expressive enough to specify the form
of improvement we need.

Consider

module Fmap where

class Fmap a b fa fb | a fb -> b fa, 
                       b fa -> a fb,
                       fa fb -> a b 
    where fmap2 :: (a->b)->(fa -> fb)


-- identity functor
instance Fmap a a a a where fmap2 h = h

e = fmap2 id 'a'

yields

Type checking      
ERROR Fmap2.hs:17 - Unresolved top-level overloading
*** Binding             : e
*** Outstanding context : Fmap c c Char b

though we would like to "improve" this type

to Fmap Char Char Char Char  where

c=Char and b=Char

 > I believe the same is true in this case.  Ccs and fds address
 > different problems.  They are complementary tools, each with their
 > own strengths and weaknesses.
 > 

I believe that a refined form of fds is able to encode Ccs.
Give me some time to provide more evidence for my unsupported claims.

Martin