[Haskell-cafe] Functional dependencies and type inference
Iavor Diatchki
iavor.diatchki at gmail.com
Thu Aug 11 20:04:35 EDT 2005
Hello,
On 8/11/05, Simon Peyton-Jones <simonpj at microsoft.com> wrote:
> ... Here is a boiled down version, much simpler to
> understand.
>
> module Proxy where
>
> class Dep a b | a -> b
> instance Dep Char Bool
>
> foo :: forall a. a -> (forall b. Dep a b => a -> b) -> Int
> foo x f = error "urk"
Should this really be valid? It seems that because 'b' is determined
by 'a' we should not be allowed to quantify over 'b' without
quantifying over 'a'. I think we can view the class 'Dep' as a
function on types, that is defined by the instances. Then the above
type is:
a -> (a -> Dep a) -> Int
and it seems that the quantification over 'b' is non-sensical.
-Iavor
More information about the Haskell-Cafe
mailing list