How Type inference work in presence of Functional Dependencies

Consider the code below : {-# LANGUAGE MultiParamTypeClasses,FlexibleInstances,FunctionalDependencies,UndecidableInstances,FlexibleContexts #-} class Foo a c | a -> c instance Foo Int Float f :: (Foo Int a) => Int -> a f = undefined Now when I see the inferred type of f in ghci
:t f
f :: Int -> Float
Now If I add the following code g :: Int -> Float g = undefined h :: (Foo Int a) => Int -> a h = g I get the error Could not deduce (a ~ Float) I am not able to understand what has happened here ? The restriction "Foo Int a" should have restricted the type of h to "Int -> Float" as shown in the inferred type of f. - Satvik

I don't know if this is a bug or not, but the translation to type
families works:
class Foo a where
type FooT a :: *
instance Foo Int where
type FooT Int = Float
f :: Int -> FooT Int
f = undefined
g :: Int -> Float
g = undefined
h :: Int -> FooT Int
h = g
You don't even need the class contexts.
Erik
On Thu, Sep 13, 2012 at 11:18 AM, satvik chauhan
Consider the code below :
{-# LANGUAGE MultiParamTypeClasses,FlexibleInstances,FunctionalDependencies,UndecidableInstances,FlexibleContexts #-} class Foo a c | a -> c instance Foo Int Float f :: (Foo Int a) => Int -> a f = undefined
Now when I see the inferred type of f in ghci
:t f
f :: Int -> Float
Now If I add the following code
g :: Int -> Float g = undefined
h :: (Foo Int a) => Int -> a h = g
I get the error
Could not deduce (a ~ Float)
I am not able to understand what has happened here ? The restriction "Foo Int a" should have restricted the type of h to "Int -> Float" as shown in the inferred type of f.
- Satvik
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Erik Hesselink
-
satvik chauhan