Messing around with types [newbie]

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

Hello Cristiano, Thursday, June 21, 2007, 4:46:27 PM, you wrote:
class FooOp a b where foo :: a -> b -> IO ()
instance FooOp Int Double where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y)
this is rather typical question :) unlike C++ which resolves any overloading at COMPILE TIME, selecting among CURRENTLY available overloaded definitions and complaining only when when this overloading is ambiguous, type classes are the RUN-TIME overloading mechanism your definition of partialFoo compiled into code which may be used with any instance of foo, not only defined in this module. so, it cannot rely on that first argument of foo is always Int because you may define other instance of FooOp in other module. "10" is really constant function of type: 10 :: (Num t) => t i.e. this function should receive dictionary of class Num in order to return value of type t (this dictionary contains fromInteger::Integer->t method which used to convert Integer representation of 10 into type actually required at this place) this means that partialFoo should have a method to deduce type of 10 in order to pass it into foo call. Let's consider its type: partialFoo :: (FooOp t y) => y -> IO () when partialFoo is called with *any* argument, there is no way to deduce type of t from type of y which means that GHC has no way to determine which type 10 in your example should have. for example, if you will define instance FooOp Int32 Double where anywhere, then call partialFoo (5.0::Double) will become ambiguous shortly speaking, overloading resolved based on global class properties, not on the few instances present in current module. OTOH, you build POLYMORPHIC functions this way while C++ just selects best-suited variant of overloaded function and hard-code its call further reading: http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps.gz http://haskell.org/haskellwiki/OOP_vs_type_classes chapter 7 of GHC user's guide, "functional dependencies" -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Cristiano,
Thursday, June 21, 2007, 4:46:27 PM, you wrote:
class FooOp a b where foo :: a -> b -> IO ()
instance FooOp Int Double where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y)
this is rather typical question :) unlike C++ which resolves any overloading at COMPILE TIME, selecting among CURRENTLY available overloaded definitions and complaining only when when this overloading is ambiguous, type classes are the RUN-TIME overloading mechanism
As I understood it, it was at COMPILE TIME (i.e. no type witness) whenever explicitly type-annotated, implicitly when not exported from a module, or when inlined at the call site, at least in GHC. Or did I get this wrong? Dan

Hello Dan, Thursday, June 21, 2007, 7:39:35 PM, you wrote:
class FooOp a b where foo :: a -> b -> IO ()
instance FooOp Int Double where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y)
this is rather typical question :) unlike C++ which resolves any overloading at COMPILE TIME, selecting among CURRENTLY available overloaded definitions and complaining only when when this overloading is ambiguous, type classes are the RUN-TIME overloading mechanism
As I understood it, it was at COMPILE TIME (i.e. no type witness) whenever explicitly type-annotated, implicitly when not exported from a module, or when inlined at the call site, at least in GHC. Or did I get this wrong?
overloading rules are general and they should work in any situation. generally speaking, you define POLYMORPHIC function which will work with any instance of FooOp class. there is no way to force GHC to use ad-hoc overloading -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 6/21/07, Cristiano Paris
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

Cristiano Paris wrote:
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)
The Haskell type classes system works in an "open world assumption": while the compiler can see the class instances in your code, it does not assume there are not others elsewhere (e.g. in another module). In your example, the compiler can not prove that the only instance matching prog = partialFoo 5.0 10 is the one you wrote, unless you restrict the numeric constants to specific types as you did. Indeed, assume that in another module there is the instance instance FooOp Double Double where foo _ _ = putStrLn "DD" what should then be the result of your program prog? 10 might be a Double after all, and "DD" could be as good a result as "5.0 Double 10". Being ambiguous, the program is rejected. Due to the open world assumption, your program is rejected as well. Regards, Zun.
participants (5)
-
Bryan Burgers
-
Bulat Ziganshin
-
Cristiano Paris
-
Dan Weston
-
Roberto Zunino