
Hi all, consider this very small function: thing n = n + round(sqrt n) It loads into ghci with no warnings. When I try to run "thing 10" I get: *Main> :load c:\temp\statictype.hs [1 of 1] Compiling Main ( C:\temp\statictype.hs, interpreted ) Ok, modules loaded: Main. *Main> thing 10 <interactive>:1:0: Ambiguous type variable `t' in the constraints: `Integral t' arising from a use of `thing' at <interactive>:1:0-7 `RealFrac t' arising from a use of `thing' at <interactive>:1:0-7 `Floating t' arising from a use of `thing' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s) I have tried to add various type signatures (without really knowing what I'm doing!) and haven't been able to get it to work. I am confused about a few things related to this: (a) what type signature fixes it and why it needs any help - it looks like the sort of thing that type inference shouldn't need any help with (b) it looks like a runtime type error and I thought you didn't get runtime type errors in Haskell (c) if I substitute 10 for n and do "10 + round(sqrt 10)" I get the expected answer 13 any help most welcome. cheers, Ivan

round returns an Integral type, but sqrt expects a Floating type
Prelude> :t sqrt
sqrt :: (Floating a) => a -> a
Prelude> :t round
round :: (RealFrac a, Integral b) => a -> b
Prelude>
Haskell's numeric type classes can be intimidating for beginners, but it
basically means you are combining floating point numbers with integer
numbers, and you must convert these numbers to the same type (just as in C#
or other languages, so that are aware of possible unwanted numerical
effects).
You can use functions like fromIntegral and realToFrac to convert numbers.
So try this
thing n = n + fromIntegral ( round(sqrt n) )
You can also get rid of the parentheses like this:
thing n = n + fromIntegral $ round $ sqrt n
On Thu, Mar 26, 2009 at 11:01 PM, Ivan Moore
Hi all,
consider this very small function:
thing n = n + round(sqrt n)
It loads into ghci with no warnings. When I try to run "thing 10" I get:
*Main> :load c:\temp\statictype.hs [1 of 1] Compiling Main ( C:\temp\statictype.hs, interpreted ) Ok, modules loaded: Main. *Main> thing 10
<interactive>:1:0: Ambiguous type variable `t' in the constraints: `Integral t' arising from a use of `thing' at <interactive>:1:0-7 `RealFrac t' arising from a use of `thing' at <interactive>:1:0-7 `Floating t' arising from a use of `thing' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s)
I have tried to add various type signatures (without really knowing what I'm doing!) and haven't been able to get it to work.
I am confused about a few things related to this: (a) what type signature fixes it and why it needs any help - it looks like the sort of thing that type inference shouldn't need any help with (b) it looks like a runtime type error and I thought you didn't get runtime type errors in Haskell (c) if I substitute 10 for n and do "10 + round(sqrt 10)" I get the expected answer 13
any help most welcome.
cheers,
Ivan _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Peter Verswyvelen wrote:
You can also get rid of the parentheses like this:
thing n = n + fromIntegral $ round $ sqrt n
I'm having a hard time finding an explanation of the dollar signs. What do they do? It looks like they break up the left-ro-right association of function names to arguments. As a beginner, I love how Haskell is filled with so many good ideas, in many areas. The basic concept of functional programming is good, but also Haskell has beautiful syntax that's just pleasing to look at, and also has many convenient features which may not quite qualify as "beautiful" or "elegant" but are just convenient (still a worthy thing). Languages that borrow from Haskell, like Python's list comprehensions, invariably are much dumbed-down implementations. In Python, list comprehensions don't have guards or pattern matching. (Technically you can put in a guard via an if statement, but you are doing a lot more typing at that point.) Thanks, Mike

On 27 Mar 2009, at 14:01, Michael Mossey wrote:
Peter Verswyvelen wrote:
You can also get rid of the parentheses like this: thing n = n + fromIntegral $ round $ sqrt n
I'm having a hard time finding an explanation of the dollar signs. What do they do? It looks like they break up the left-ro-right association of function names to arguments.
You're pretty much there! The $ function is simply "apply": f $ a = f a The difference is that this version of application (as opposed to the version written as ' ') has very very low precidence, and can be used to essentially mean "apply this to the whole expression on my right". Of note though, using chains of ($)s as peter did is commonly considered bad style, instead, one should use (.) to build up a function, and then apply it, so not: fromIntegral $ round $ sqrt n But instead: fromIntegral . round . sqrt $ n Why? Because the latter one has more valid expressions and is therefor easier to refactor. For example, in the latter one I may deside that (round . sqrt) is a useful function in itself (lets call it integralSqrt) and refactor: fromIntegral . integralSqrt $ n integralSqrt = round . sqrt With this style, this is simply a matter of copy/paste.
As a beginner, I love how Haskell is filled with so many good ideas, in many areas. The basic concept of functional programming is good, but also Haskell has beautiful syntax that's just pleasing to look at, and also has many convenient features which may not quite qualify as "beautiful" or "elegant" but are just convenient (still a worthy thing).
I'm not sure, most of the convenient things I use in Haskell are also beautiful and elegant, did you have something in mind? Thanks Bob

On Fri, Mar 27, 2009 at 06:01:15AM -0700, Michael Mossey wrote:
Peter Verswyvelen wrote:
You can also get rid of the parentheses like this: thing n = n + fromIntegral $ round $ sqrt n
I'm having a hard time finding an explanation of the dollar signs. What do they do? It looks like they break up the left-ro-right association of function names to arguments.
($) is just function application. It is defined as: f $ x = f x This looks useless, of course, but it also has very low precedence, so it is often used to avoid parentheses. For example, (foo bar) (baz t) can't be written without the parentheses, since that would be parsed as ((foo bar) baz) t, but it can be written as foo bar $ baz t
As a beginner, I love how Haskell is filled with so many good ideas, in many areas. The basic concept of functional programming is good, but also Haskell has beautiful syntax that's just pleasing to look at, and also has many convenient features which may not quite qualify as "beautiful" or "elegant" but are just convenient (still a worthy thing).
As a non-beginner, I love this too. So I think you're on to something. =) -Brent

On Fri, 27 Mar 2009, Brent Yorgey wrote:
thing n = n + fromIntegral (round (sqrt n))
thing :: Floating a => a -> a
thing n = n + round (sqrt (fromIntegral n))
thing :: Integral a => a -> a That is, the return types of the method are different?
Pop quiz for beginners: both of these solve the original problem, but they are not quite the same. What is the difference? (Do not answer this question if you are not a beginner!)

On Fri, Mar 27, 2009 at 11:28:54AM -0400, Edward Z. Yang wrote:
On Fri, 27 Mar 2009, Brent Yorgey wrote:
thing n = n + fromIntegral (round (sqrt n))
thing :: Floating a => a -> a
thing n = n + round (sqrt (fromIntegral n))
thing :: Integral a => a -> a
That is, the return types of the method are different?
Right! -Brent

On Thu, Mar 26, 2009 at 10:01:07PM +0000, Ivan Moore wrote:
Hi all,
consider this very small function:
thing n = n + round(sqrt n)
Here's what's going on: since you call sqrt on n, it must have some type which is an instance of Floating. However, round can return any type which is an instance of Integral, and since you are adding n to it, n must have the same type. This is the takeaway point here: sqrt requires some floating-point type (like Float or Double), but round returns an Integral type (like Int or Integer) and n can't be both. In particular you can't call sqrt on an Integral value. So the fix is to use fromIntegral to convert: thing n = n + round (sqrt (fromIntegral n))
It loads into ghci with no warnings.
The reason (which is a bit confusing) is that it typechecks just fine---if there *were* a type which is an instance of both Integral and Floating (and I guess round needs RealFrac as well), n could have that type. There isn't such a type in the standard libraries, but in theory you could make up your own type which is an instance of both.
When I try to run "thing 10" I get:
*Main> :load c:\temp\statictype.hs [1 of 1] Compiling Main ( C:\temp\statictype.hs, interpreted ) Ok, modules loaded: Main. *Main> thing 10
<interactive>:1:0: Ambiguous type variable `t' in the constraints: `Integral t' arising from a use of `thing' at <interactive>:1:0-7 `RealFrac t' arising from a use of `thing' at <interactive>:1:0-7 `Floating t' arising from a use of `thing' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s)
I have tried to add various type signatures (without really knowing what I'm doing!) and haven't been able to get it to work.
I am confused about a few things related to this: (a) what type signature fixes it and why it needs any help - it looks like the sort of thing that type inference shouldn't need any help with
The error message is particularly unhelpful here. Adding a type signature would only help if you actually had some type which was both Integral and Floating, but you don't.
(b) it looks like a runtime type error and I thought you didn't get runtime type errors in Haskell
You don't. This isn't a runtime type error; the error was generated while trying to typecheck the expression 'thing 10' before evaluating it.
(c) if I substitute 10 for n and do "10 + round(sqrt 10)" I get the expected answer 13
This is because numeric literals (like 10) are polymorphic---they can have any numeric type. In this case, type inference correctly figures out that the first 10 should have type Integer, and the second 10 should have type Double. The difference is that they are not constrained to have the same type---unlike the two occurrences of 'n' in your original function. Confusing, isn't it! It's a shame that numeric types can be so confusing, since that's usually one of the first things that people run into when learning the language. But I hope this is helpful. Feel free to ask if you have more questions. -Brent

Many thanks for the fantastic answers. I have a question related to your answer
The reason (which is a bit confusing) is that it typechecks just fine---if there *were* a type which is an instance of both Integral and Floating (and I guess round needs RealFrac as well), n could have that type. There isn't such a type in the standard libraries, but in theory you could make up your own type which is an instance of both.
If there were such a type, could "10" have that type and then would my
problem have not existed? (in which case, why doesn't it!?)
(an answer of - "ask again when you've used the language a bit more"
would be perfectly fine if it requires a lot
more understanding of the language to understand the answer than a
newbie like me has - I'm just curious)
On Fri, Mar 27, 2009 at 1:07 PM, Brent Yorgey
On Thu, Mar 26, 2009 at 10:01:07PM +0000, Ivan Moore wrote:
Hi all,
consider this very small function:
thing n = n + round(sqrt n)
Here's what's going on: since you call sqrt on n, it must have some type which is an instance of Floating. However, round can return any type which is an instance of Integral, and since you are adding n to it, n must have the same type.
This is the takeaway point here: sqrt requires some floating-point type (like Float or Double), but round returns an Integral type (like Int or Integer) and n can't be both. In particular you can't call sqrt on an Integral value. So the fix is to use fromIntegral to convert:
thing n = n + round (sqrt (fromIntegral n))
It loads into ghci with no warnings.
The reason (which is a bit confusing) is that it typechecks just fine---if there *were* a type which is an instance of both Integral and Floating (and I guess round needs RealFrac as well), n could have that type. There isn't such a type in the standard libraries, but in theory you could make up your own type which is an instance of both.
When I try to run "thing 10" I get:
*Main> :load c:\temp\statictype.hs [1 of 1] Compiling Main ( C:\temp\statictype.hs, interpreted ) Ok, modules loaded: Main. *Main> thing 10
<interactive>:1:0: Ambiguous type variable `t' in the constraints: `Integral t' arising from a use of `thing' at <interactive>:1:0-7 `RealFrac t' arising from a use of `thing' at <interactive>:1:0-7 `Floating t' arising from a use of `thing' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s)
I have tried to add various type signatures (without really knowing what I'm doing!) and haven't been able to get it to work.
I am confused about a few things related to this: (a) what type signature fixes it and why it needs any help - it looks like the sort of thing that type inference shouldn't need any help with
The error message is particularly unhelpful here. Adding a type signature would only help if you actually had some type which was both Integral and Floating, but you don't.
(b) it looks like a runtime type error and I thought you didn't get runtime type errors in Haskell
You don't. This isn't a runtime type error; the error was generated while trying to typecheck the expression 'thing 10' before evaluating it.
(c) if I substitute 10 for n and do "10 + round(sqrt 10)" I get the expected answer 13
This is because numeric literals (like 10) are polymorphic---they can have any numeric type. In this case, type inference correctly figures out that the first 10 should have type Integer, and the second 10 should have type Double. The difference is that they are not constrained to have the same type---unlike the two occurrences of 'n' in your original function.
Confusing, isn't it! It's a shame that numeric types can be so confusing, since that's usually one of the first things that people run into when learning the language. But I hope this is helpful. Feel free to ask if you have more questions.
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, Mar 27, 2009 at 07:44:05PM +0000, Ivan Moore wrote:
Many thanks for the fantastic answers.
I have a question related to your answer
The reason (which is a bit confusing) is that it typechecks just fine---if there *were* a type which is an instance of both Integral and Floating (and I guess round needs RealFrac as well), n could have that type. There isn't such a type in the standard libraries, but in theory you could make up your own type which is an instance of both.
If there were such a type, could "10" have that type and then would my problem have not existed? (in which case, why doesn't it!?) (an answer of - "ask again when you've used the language a bit more" would be perfectly fine if it requires a lot more understanding of the language to understand the answer than a newbie like me has - I'm just curious)
If there were such a type, and if it were one of the types to which ghci was allowed to default, then you would not have had a problem. But if you look at the methods of the Integral and Floating classes, you will see that such a type would likely be silly. You can't really have a type which is simultaneously Integral (i.e. whole numbers, with no fractional part) and Floating (i.e. floating point numbers which can be divided, square rooted, etc.). To have a type be an instance of both would require a radical reinterpretation of what these type classes mean. -Brent

2009/03/27 Ivan Moore
The reason (which is a bit confusing) is that it typechecks just fine---if there *were* a type which is an instance of both Integral and Floating (and I guess round needs RealFrac as well), n could have that type. There isn't such a type in the standard libraries, but in theory you could make up your own type which is an instance of both.
If there were such a type, could "10" have that type and then would my problem have not existed?
Yes, that is correct.
in which case, why doesn't it!?
Does it actually make any logical sense for a type to be both integral (governed by rules of modular division) and floating point (governed by rules of IEEE 754 division)? -- Jason Dusek

without engaging my brain too much, given what you've said, then why
is "10" both integral and floating point? why not "10" being integral
and "10.0" being floating point?
On Tue, Mar 31, 2009 at 2:09 AM, Jason Dusek
2009/03/27 Ivan Moore
: The reason (which is a bit confusing) is that it typechecks just fine---if there *were* a type which is an instance of both Integral and Floating (and I guess round needs RealFrac as well), n could have that type. There isn't such a type in the standard libraries, but in theory you could make up your own type which is an instance of both.
If there were such a type, could "10" have that type and then would my problem have not existed?
Yes, that is correct.
in which case, why doesn't it!?
Does it actually make any logical sense for a type to be both integral (governed by rules of modular division) and floating point (governed by rules of IEEE 754 division)?
-- Jason Dusek

Ivan,
without engaging my brain too much, given what you've said, then why is "10" both integral and floating point? why not "10" being integral and "10.0" being floating point?
The literal "10", as it appears in Haskell source, stands for something that can take on any numeric type, but as soon as you use it in a context that constrains it, well, it gets constrained! "10" can be integral, or it can be floating point. As I think Jason was saying, *if* there was a type that was both integral and floating point, then 10 could represent something of that type. But there's no *sensible* type that has both integral and floating point nature. (At least none that comes to mind. Maybe you could do something with symbolic manipulation that would make sense.) Leaving behind sensible types, we can define one that's both integral and fractional. I'm going to violate all kinds of commonly assumed (but unenforced) laws of the numeric classes, in an act of self-loathing, so enjoy the following abomination! The code is appended at the end of this message. dorsey@elwood:~/src/scratch$ ghci int-float.hs *Main> :t munge munge :: IntFloat -> IntFloat *Main> :t munge 10 munge 10 :: IntFloat *Main> fromIntegral (munge 10) 42 If you look at the code for munge below, you'll see that I've mixed integral operations (div) with floating point operations (**) and fractional operations (/). I have no trouble applying munge to 10. The literal "10" (which really means "fromIntegral 10") takes on the right type because it has to to match munge's argument type. So why would I choose to do this terrible thing? To illustrate that: 1) The open world assumption of Haskell type classes implies that a type like this could be definied later, even if it doesn't exist now. 2) Even though you can do this and obey the type rules, I had to use a silly type, with very silly class instance definitions. Integral things just aren't fractional! To answer you other specific question, about why they didn't just distinguish "10" from "10.0" as some other languages do, the original motivation was well before my time. But it does seem to me that being able to use "10" to refer not only to Integers and Floats, but also to Ints, Int16s, Doubles, and many unforseen numeric types, was a clever choice. Sadly, numeric literals make the short-list of things that confuse Haskell neophites the most. I hope all this is at least either interesting or helpful. Regards, John -- int-float.hs -- a datatype inhabiting floating and integral classes, -- but which doesn't model numerics particularly well data IntFloat = IF String deriving (Show, Eq, Ord) munge :: IntFloat -> IntFloat munge x = x / x `div` x ** x instance Num IntFloat where _ + _ = IF "sum" _ - _ = IF "difference" _ * _ = IF "product" negate _ = IF "negation" abs _ = IF "abs" signum _ = IF "signum" fromInteger _ = IF "fromInteger" instance Integral IntFloat where quot _ _ = IF "quot" rem _ _ = IF "rem" div _ _ = IF "div" mod _ _ = IF "mod" quotRem _ _ = (IF "quotRem quot", IF "quotRem rem") divMod _ _ = (IF "divMod div", IF "divMod mod") toInteger _ = 42 instance Floating IntFloat where pi = IF "pi" exp _ = IF "exp" sqrt _ = IF "sqrt" log _ = IF "log" (**) _ _ = IF "**" logBase _ _ = IF "logBase" sin _ = IF "sin" tan _ = IF "tan" cos _ = IF "cos" asin _ = IF "asin" atan _ = IF "atan" acos _ = IF "acos" sinh _ = IF "sinh" tanh _ = IF "tanh" cosh _ = IF "cosh" asinh _ = IF "asinh" atanh _ = IF "atanh" acosh _ = IF "acosh" instance Real IntFloat where toRational _ = toRational 42 instance Enum IntFloat where succ _ = IF "succ" pred _ = IF "pred" toEnum _ = IF "toEnum" fromEnum _ = 42 enumFrom _ = [IF "enumFrom"] enumFromThen _ _ = [IF "enumFromThen"] enumFromTo _ _ = [IF "enumFromTo"] enumFromThenTo _ _ _ = [IF "enumFromThenTo"] instance Fractional IntFloat where (/) _ _ = IF "/" recip _ = IF "recip" fromRational _ = IF "fromRational"
participants (8)
-
Brent Yorgey
-
Edward Z. Yang
-
Ivan Moore
-
Jason Dusek
-
John Dorsey
-
Michael Mossey
-
Peter Verswyvelen
-
Thomas Davie