existential types and functional dependencies

Christian Maeder maeder@tzi.de
Thu, 20 Mar 2003 19:40:06 +0100


The following module is accepted by ghc (with -fglasgow-exts) but 
rejected by hugs:

module ParseAny where

class Syntax tag as | tag -> as where
     parse :: tag -> String -> as

data AnyAs = forall tag as. Syntax tag as =>
	     MkAs tag as

data AnyTag = forall tag as. Syntax tag as =>
	      MkTag tag

parseAny :: AnyTag -> String -> AnyAs
parseAny (MkTag tag) str = MkAs tag $ parse tag str

-- -------------------------------------------------------

Hugs mode: Restart with command line option +98 for Haskell 98 mode

Reading file "/home/linux-bkb/hugs/lib/hugs/libraries/Hugs/Prelude.hs":
Reading file "/home/linux-bkb/hugs/lib/hugs/libraries/Prelude.hs":
Reading file "ParseAny.hs":
Type checking
ERROR "ParseAny.hs":13 - Cannot justify constraints in explicitly typed 
binding
*** Expression    : parseAny
*** Type          : AnyTag -> String -> AnyAs
*** Given context : ()
*** Constraints   : Syntax _0 a

When I omit the functional dependency "| tag -> as", ghc yields a 
similar error

Cheers Christian