fundeps help
Ganesh Sittampalam
ganesh at earth.li
Sat Dec 1 18:08:56 EST 2007
Hi,
I'm trying to understand what fundeps do and don't let me do. One
particular source of confusion is why the following program doesn't
typecheck:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module Fundeps where
class Dep a b | a -> b, b -> a
conv :: (Dep a b1,Dep a b2) => b1 -> b2
conv = id
{- end of program -}
It seems as if inferring that b1 = b2 is precisely what "improvement" is
about, but I'm not really sure when GHC actually applies that. Is there
any documentation of that? I've read Mark Jones' paper, the haskell-prime
wiki entry about Fundeps and the GHC manual but am still rather lost.
Cheers,
Ganesh
More information about the Glasgow-haskell-users
mailing list