On 6/21/07, Cristiano Paris <[EMAIL PROTECTED]> wrote:
Hi,

I'm making my way through Haskell which seems to me one of the languages
with steepest learning curve around.

Now, please consider this snippet:

{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where


class FooOp a b where
  foo :: a -> b -> IO ()

instance FooOp Int Double where
  foo x y = putStrLn $ (show x) ++ " Double " ++ (show y)

partialFoo = foo (10::Int)

bar = partialFoo (5.0::Double)

I hope the indentation looks ok in your email client. I'm experimenting with
currying and typeclasses at the moment.

 If I try to import this in ghci, it works flawlessy. Now, if I remove the
type signature from 10 and 5.0, ghci complaints saying:

example.hs:12:6:
    Ambiguous type variable `t' in the constraint:
      `Num t' arising from use of `partialFoo' at example.hs:12:6-19
    Probable fix: add a type signature that fixes these type variable(s)

example.hs:12:6:
    Ambiguous type variables `t', `t1' in the constraint:
      `FooOp t t1' arising from use of `partialFoo' at example.hs:12:6-19
    Probable fix: add a type signature that fixes these type variable(s)

example.hs:12:17:
    Ambiguous type variable `t1' in the constraint:
      `Fractional t1'
        arising from the literal `5.0' at example.hs:12:17-19
    Probable fix: add a type signature that fixes these type variable(s)

I switched off the monomorphism restriction (btw, is this bad? No flame war
please :D) otherwise it'd have complained louder.

Can you explain how to fix the code (if possible) and give some explanation?

Here's a quick transcript of a GHCi session:

Prelude> :t 10
10 :: (Num t) => t
Prelude> :t 5.0
5.0 :: (Fractional t) => t

From this you can see that 10 is not necessarily an Int, and 5.0 is
not necessarily a Double. So the typechecker does not know, given just
10 and 5.0, which instance of 'foo' to use. But when you explicitly
told the typechecker that 10 is an Int and 5.0 is a Double, then the
type checker was able to choose which instance of 'foo' it should use.

Does that make sense? (I hope it makes sense, and I also hope it is correct!)

And I do not really know how to fix it, maybe somebody else can write
about that.

Bryan Burgers
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to