[Haskell-cafe] Messing around with types [newbie]
Cristiano Paris
cristiano.paris.ml at gmail.com
Thu Jun 21 08:46:27 EDT 2007
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?
Thanks,
Cristiano
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070621/4d072672/attachment.htm
More information about the Haskell-Cafe
mailing list