Defaulting the following constraint ....

Hi I have something like this - purpose is that I need to drop redundant .0 in a whole number - so to show 1.2345 as 1.2345 and to show 1.0 as 1 module Test where niceShow x = if (isInt x) then show (floor x) else show x isInt x = x == fromInteger (floor x) But the hlint in my vim plugin keeps warning me that test.hs|3 col 38 warning| Defaulting the following constraint(s) to type `Integer' || (Integral a0) arising from a use of `floor' at /tmp/test.hs:3:38-42 || (Show a0) arising from a use of `show' at /tmp/test.hs:3:32-35 || In the first argument of `show', namely `(floor x)' || In the expression: show (floor x) || In the expression: if (isInt x) then show (floor x) else show x What does this mean? And what would I need to do in order to prevent this warning?

On Mon, Sep 30, 2013 at 1:06 PM, Alan Buxton
Hi****
** **
I have something like this – purpose is that I need to drop redundant .0 in a whole number – so to show 1.2345 as 1.2345 and to show 1.0 as 1****
** **
*module Test where*
* *
*niceShow x = if (isInt x) then show (floor x) else show x*
* *
*isInt x = x == fromInteger (floor x)*****
**
But the hlint in my vim plugin keeps warning me that****
** **
test.hs|3 col 38 warning| Defaulting the following constraint(s) to type `Integer'****
|| (Integral a0) arising from a use of `floor' at /tmp/test.hs:3:38-42****
|| (Show a0) arising from a use of `show' at /tmp/test.hs:3:32-35****
|| In the first argument of `show', namely `(floor x)'****
|| In the expression: show (floor x)****
|| In the expression: if (isInt x) then show (floor x) else show x****
** **
What does this mean? And what would I need to do in order to prevent this warning?****
It looks like you have a type mismatch in `isInt`, floor returns a type in the typeclass Integral (this may or may not be an Integer) but fromInteger demands its input be an Integer. Here are the type sigs: ghci> :t floor floor :: (Integral b, RealFrac a) => a -> b ghci> :t fromIntegral fromIntegral :: (Integral a, Num b) => a -> b Changing `fromInteger` to `fromIntegeral` should fix this problem. It will also help if you write down type signatures explicitly for your two functions. -- Benjamin Jones

It is because you do a floor on x, returning a where a is an Integral, but
which Integral is it? Is it an Int or an Integer? Well it decides to
default it to integer because that is what ghci does as it is the safe
option, but it decided to warn you about it just so you are aware.
Afterall integers are slower than ints, and you might have wanted an int.
You can silence the warning by telling it what to do:
niceShow x = if (isInt x) then show (floor x :: Int) else show x
niceShow x = if (isInt x) then show (floor x :: Integer) else show x
On Mon, Sep 30, 2013 at 4:06 PM, Alan Buxton
Hi****
** **
I have something like this – purpose is that I need to drop redundant .0 in a whole number – so to show 1.2345 as 1.2345 and to show 1.0 as 1****
** **
*module Test where*
* *
*niceShow x = if (isInt x) then show (floor x) else show x*
* *
*isInt x = x == fromInteger (floor x)*****
**
But the hlint in my vim plugin keeps warning me that****
** **
test.hs|3 col 38 warning| Defaulting the following constraint(s) to type `Integer'****
|| (Integral a0) arising from a use of `floor' at /tmp/test.hs:3:38-42****
|| (Show a0) arising from a use of `show' at /tmp/test.hs:3:32-35****
|| In the first argument of `show', namely `(floor x)'****
|| In the expression: show (floor x)****
|| In the expression: if (isInt x) then show (floor x) else show x****
** **
What does this mean? And what would I need to do in order to prevent this warning?****
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thanks for the help. I now have another question related to this.
When I write:
isInt :: Double -> Bool
isInt x = x == fromInteger (floor x)
niceShow :: Double -> String
niceShow x = if isInt x then show (floor x :: Int) else show x
I get a warning about a "too strict if". If I then follow the recommendation
and change niceShow to be
show (if isInt x then (floor x :: Int) else x)
Then I get an error that Couldn't match expected type `Int' with actual type
`Double' which makes sense because floor x :: Int produces an Int but x
alone is a Double. Surely hlint could have figured this out from the type
signatures and not made the recommendation to change my if structure?
What's going on here? And what best to do? What is a "too strict if" anyway?
a
From: Beginners [mailto:beginners-bounces@haskell.org] On Behalf Of David
McBride
Sent: 30 September 2013 21:54
To: The Haskell-Beginners Mailing List - Discussion of primarily
beginner-level topics related to Haskell
Subject: Re: [Haskell-beginners] Defaulting the following constraint ....
It is because you do a floor on x, returning a where a is an Integral, but
which Integral is it? Is it an Int or an Integer? Well it decides to
default it to integer because that is what ghci does as it is the safe
option, but it decided to warn you about it just so you are aware. Afterall
integers are slower than ints, and you might have wanted an int. You can
silence the warning by telling it what to do:
niceShow x = if (isInt x) then show (floor x :: Int) else show x
niceShow x = if (isInt x) then show (floor x :: Integer) else show x
On Mon, Sep 30, 2013 at 4:06 PM, Alan Buxton

On Thu, Oct 3, 2013 at 1:52 PM, Alan Buxton
niceShow x = if isInt x then show (floor x :: Int) else show x
** **
I get a warning about a “too strict if”. If I then follow the recommendation and change niceShow to be****
** **
show (if isInt x then (floor x :: Int) else x)****
** **
Then I get an error that *Couldn't match expected type `Int' with actual type `Double'* which makes sense because floor x :: Int produces an Int but x alone is a Double. Surely hlint could have figured this out from the type signatures and not made the recommendation to change my if structure? ****
**
hlint doesn't recognize types, only code structure to some extent (it is a parser, not a compiler). As such, it will sometimes produce bad advice like that. "Too strict if" pretty much means what you saw... that you have the same structure in both legs and it thinks you should abstract it out. But, as I noted, it doesn't know about types so it can't recognize that you can't type the refactored expression. In fact I'd generally claim that "Too strict if" is by far its worst designed diagnostic, because of its inability to recognize types and because the resulting message is incomprehensible. In short, take hlint's diagnostics with several grains of salt. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Thanks a lot
Best
A
Από το iPad μου
3 Oct 2013, 19:33, ο/η Brandon Allbery
On Thu, Oct 3, 2013 at 1:52 PM, Alan Buxton
wrote: niceShow x = if isInt x then show (floor x :: Int) else show x I get a warning about a “too strict if”. If I then follow the recommendation and change niceShow to be
show (if isInt x then (floor x :: Int) else x)
Then I get an error that Couldn't match expected type `Int' with actual type `Double' which makes sense because floor x :: Int produces an Int but x alone is a Double. Surely hlint could have figured this out from the type signatures and not made the recommendation to change my if structure?
hlint doesn't recognize types, only code structure to some extent (it is a parser, not a compiler). As such, it will sometimes produce bad advice like that.
"Too strict if" pretty much means what you saw... that you have the same structure in both legs and it thinks you should abstract it out. But, as I noted, it doesn't know about types so it can't recognize that you can't type the refactored expression. In fact I'd generally claim that "Too strict if" is by far its worst designed diagnostic, because of its inability to recognize types and because the resulting message is incomprehensible.
In short, take hlint's diagnostics with several grains of salt.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
Alan Buxton
-
Benjamin Jones
-
Brandon Allbery
-
David McBride