Lennart Augustsson:
In the current GHC there are even definitions that are perfecty
usable, that cannot be given the type signature that that was
inferred.
That's bad, I agree.
At work we have the warning for missing signatures enabled, and we
turn warnings into errors. We have to disbale this for certain
definitions, because you cannot give them a signature. I find that
broken.
Definitely. Can you give an example?
Manuel
On Thu, Apr 10, 2008 at 5:52 AM, Manuel M T Chakravarty <[EMAIL PROTECTED]
> wrote:
Lennart Augustsson:
Let's look at this example from a higher level.
Haskell is a language which allows you to write type signatures for
functions, and even encourages you to do it.
Sometimes you even have to do it. Any language feature that stops
me from writing a type signature is in my opinion broken.
TFs as implemented in currently implemented ghc stops me from
writing type signatures. They are thus, in my opinion, broken.
The problem of ambiguity is not at all restricted to TFs. In fact,
you need neither TFs nor FDs to get the exact same behaviour. You
don't even need MPTCs:
{-# LANGUAGE FlexibleContexts #-}
module Ambiguity where
class C a
bar :: C (a, b) => b -> b
bar = id
bar' :: C (a, b) => b -> b
bar' = bar
This gives us
/Users/chak/Code/haskell/Ambiguity.hs:10:7:
Could not deduce (C (a, b)) from the context (C (a1, b))
arising from a use of `bar'
at /Users/chak/Code/haskell/Ambiguity.hs:10:7-9
Possible fix:
add (C (a, b)) to the context of the type signature for `bar''
or add an instance declaration for (C (a, b))
In the expression: bar
In the definition of `bar'': bar' = bar
So, we have this problem as soon as we have flexible contexts and/or
MPTCs, independent of TFs and FDs.
Manuel
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe