numerical types, the $ operator

Hi all I'm trying to understand the following simple function
-- | fractional part of number. frac :: (RealFrac a) => a -> a frac x = x - fromInteger . floor $ x
which apparently is wrong. Whereas this is ok
frac x = x - fromInteger (floor x)
Is the 1st one wrong because it is trying to apply the _whole_ 'left of $' to the 'x' on the right? How would an experienced guy write this without parentheses? Moreover, I've put the 'RealFrac' by looking at ":t floor". What kind of class constraint whould you put for doing eg:
frac x = x - fromInteger (floor (sqrt x) )
since 'floor' takes fractional and 'sqrt' takes RealFrac? Some kind of super-class? Thank you. PS Seems that types are half the language, if not more .. -- TG cowscanfly@airpost.net -- http://www.fastmail.fm - Access your email from home and the web

On Sat, Mar 28, 2009 at 11:18:46PM +0200, TG wrote:
Hi all I'm trying to understand the following simple function
-- | fractional part of number. frac :: (RealFrac a) => a -> a frac x = x - fromInteger . floor $ x
which apparently is wrong. Whereas this is ok
frac x = x - fromInteger (floor x)
Is the 1st one wrong because it is trying to apply the _whole_ 'left of $' to the 'x' on the right?
Exactly. ($) has very low precedence, even lower than (-).
How would an experienced guy write this without parentheses?
I'm fairly certain it's impossible to write it without using parentheses. I would probably just write x - fromInteger (floor x)
Moreover, I've put the 'RealFrac' by looking at ":t floor". What kind of class constraint whould you put for doing eg:
frac x = x - fromInteger (floor (sqrt x) )
since 'floor' takes fractional and 'sqrt' takes RealFrac? Some kind of super-class?
Every instance of RealFrac must also be an instance of Fractional, so just putting RealFrac would be fine. (And I didn't have this memorized, I just started up ghci and typed ':info Fractional' and ':info RealFrac' to see how they are declared.)
Seems that types are half the language, if not more ..
I think you're on to something there. One of the great strengths of Haskell is its strong, expressive static type system. Type classes are an especially nifty feature. Unfortunately, the numeric class hierarchy leaves a bit to be desired at times, so I hope you won't draw too many general conclusions from frustrations with numeric stuff. =) -Brent

How would an experienced guy write this without parentheses?
I'm fairly certain it's impossible to write it without using parentheses. I would probably just write
x - fromInteger (floor x)
Never impossible! flip subtract x . fromInteger $ floor x case floor x of y -> x - fromInteger y let y = floor x in x - fromInteger y I guess I wouldn't choose any of these for readability, though. Brent's version is succinct. Cheers, John

On Sat, Mar 28, 2009 at 05:53:54PM -0400, John Dorsey wrote:
How would an experienced guy write this without parentheses?
I'm fairly certain it's impossible to write it without using parentheses. I would probably just write
x - fromInteger (floor x)
Never impossible!
flip subtract x . fromInteger $ floor x case floor x of y -> x - fromInteger y let y = floor x in x - fromInteger y
Hah, you fell right into my trap! ;) Well, I actually hadn't thought of these, but I figured someone would find a way to do it.
I guess I wouldn't choose any of these for readability, though. Brent's version is succinct.
Right, the point being, parentheses are not something to be avoided at all costs. They should be used as much as necessary to aid readability, no more, no less. -Brent

On Sat, Mar 28, 2009 at 4:53 PM, John Dorsey
How would an experienced guy write this without parentheses?
I'm fairly certain it's impossible to write it without using parentheses. I would probably just write
x - fromInteger (floor x)
Never impossible!
flip subtract x . fromInteger $ floor x case floor x of y -> x - fromInteger y let y = floor x in x - fromInteger y
I'm a bit of a beginner myself, but I came up with this: let (|>) x f = f x let mapping f x = (x, f x) let mapping2 f (x,y) = (x, f y) let frac x = x |> mapping id |> mapping2 floor |> mapping2 fromInteger |> uncurry (-) A little extreme, but I still like that it illustrates the |> operator, which is actually really useful, I borrowed the concept from F#. I redefined it because I actually have no idea if F# has a similar operator. Does it? It's obviously still easier to read the original parenthesized version, but sometimes the |> operator really makes things very readable, because it emphasizes the fact that you start with a single value, and send that value through a series of transformations one after the other, and you can read each transformation in the order that it happens, rather than with function composition where you have to scan to the end first to see which operation gets applied first.

On Sun, Mar 29, 2009 at 06:02:14PM -0500, Zachary Turner wrote:
On Sun, Mar 29, 2009 at 5:53 PM, Zachary Turner
wrote: I redefined it because I actually have no idea if F# has a similar operator. Does it?
Doh, I actually meant to say I have no idea if Haskell has a similar operator.
Not defined in the standard libraries. There is, however, the (>>>) operator (from Control.Arrow) which composes functions in the opposite order. But then you still have to put the value the functions are applied to at the end. I like your (|>) operator. -Brent

Am Montag 30 März 2009 00:53:15 schrieb Zachary Turner:
On Sat, Mar 28, 2009 at 4:53 PM, John Dorsey
wrote: How would an experienced guy write this without parentheses?
I'm fairly certain it's impossible to write it without using parentheses. I would probably just write
x - fromInteger (floor x)
Never impossible!
flip subtract x . fromInteger $ floor x case floor x of y -> x - fromInteger y let y = floor x in x - fromInteger y
I'm a bit of a beginner myself, but I came up with this:
let (|>) x f = f x let mapping f x = (x, f x) let mapping2 f (x,y) = (x, f y) let frac x = x |> mapping id |> mapping2 floor |> mapping2 fromInteger |> uncurry (-)
But John didn't use (-) x . fromInteger . floor $ x because it has parentheses, like your version :) That is easily fixed, though, and since almost everything you ever need has already been coded by somebody else, let's use a library instead of (|>), mapping and mapping2: import Control.Arrow frac :: RealFrac a => a -> a frac = fromInteger . floor &&& id >>> uncurry subtract pointfree and without parentheses. f &&& g = \x -> (f x, g x) (for functions, it's more generally applicable to arrows), so your 'mapping f' is 'id &&& f', your 'mapping2 f' would be 'second f', also defined in Control.Arrow. You see that these functions are so generally useful that they already are in a library :) (>>>) is forward composition (for functions, it's defined in Control.Category for more general settings), useful and readable. You can't use it to inject the value into the pipeline, though. But often that is not necessary and pointfree style is equally readable (sometimes even more readable).
A little extreme, but I still like that it illustrates the |> operator, which is actually really useful, I borrowed the concept from F#. I redefined it because I actually have no idea if F# has a similar operator. Does it? It's obviously still easier to read the original parenthesized version, but sometimes the |> operator really makes things very readable, because it emphasizes the fact that you start with a single value, and send that value through a series of transformations one after the other, and you can read each transformation in the order that it happens, rather than with function composition where you have to scan to the end first to see which operation gets applied first.

On Sun, Mar 29, 2009 at 6:47 PM, Daniel Fischer
Am Montag 30 März 2009 00:53:15 schrieb Zachary Turner:
On Sat, Mar 28, 2009 at 4:53 PM, John Dorsey
wrote: How would an experienced guy write this without parentheses?
I'm fairly certain it's impossible to write it without using parentheses. I would probably just write
x - fromInteger (floor x)
Never impossible!
flip subtract x . fromInteger $ floor x case floor x of y -> x - fromInteger y let y = floor x in x - fromInteger y
I'm a bit of a beginner myself, but I came up with this:
let (|>) x f = f x let mapping f x = (x, f x) let mapping2 f (x,y) = (x, f y) let frac x = x |> mapping id |> mapping2 floor |> mapping2 fromInteger |> uncurry (-)
But John didn't use
(-) x . fromInteger . floor $ x
because it has parentheses, like your version :) That is easily fixed, though, and since almost everything you ever need has already been coded by somebody else, let's use a library instead of (|>), mapping and mapping2:
import Control.Arrow
frac :: RealFrac a => a -> a frac = fromInteger . floor &&& id >>> uncurry subtract
pointfree and without parentheses.
f &&& g = \x -> (f x, g x) (for functions, it's more generally applicable to arrows), so your 'mapping f' is 'id &&& f', your 'mapping2 f' would be 'second f', also defined in Control.Arrow. You see that these functions are so generally useful that they already are in a library :)
(>>>) is forward composition (for functions, it's defined in Control.Category for more general settings), useful and readable. You can't use it to inject the value into the pipeline, though. But often that is not necessary and pointfree style is equally readable (sometimes even more readable).
A little extreme, but I still like that it illustrates the |> operator, which is actually really useful, I borrowed the concept from F#. I redefined it because I actually have no idea if F# has a similar
operator.
Does it? It's obviously still easier to read the original parenthesized version, but sometimes the |> operator really makes things very readable, because it emphasizes the fact that you start with a single value, and send that value through a series of transformations one after the other, and you can read each transformation in the order that it happens, rather than with function composition where you have to scan to the end first to see which operation gets applied first.
The &&& operator is pretty sweet, thanks for pointing it out. That's pretty much what I was trying to come up with the mapping and mapping2, but it's more general and hence more useful. The "pipelining" operator I defined should definitely be used with care. For example, it requires the pipelined argument to be the last argument, which is not always the case. And I've also found that with it I tend to think about the problem less, and write less efficient code as a result. For example given a list of integers, an easy and very readable way to remove all multiples of 2 from a list, and then double the remaining items could be like this: let doit x = x |> filter (\y -> y `mod` 2 == 0) |> map (* 2) as opposed to the more efficient doit [] = [] doit (x:xs) | (x `mod` 2 == 0) = doit xs doit (x:xs) = (2 * x) : doit xs since the list is walked twice. (I'm betting someone will respond with a cool one-liner here involving function composition or something else that I can't think of yet :)

2009/3/29 Zachary Turner
The "pipelining" operator I defined should definitely be used with care. For example, it requires the pipelined argument to be the last argument, which is not always the case. And I've also found that with it I tend to think about the problem less, and write less efficient code as a result. For example given a list of integers, an easy and very readable way to remove all multiples of 2 from a list, and then double the remaining items could be like this:
let doit x = x |> filter (\y -> y `mod` 2 == 0) |> map (* 2)
as opposed to the more efficient
doit [] = [] doit (x:xs) | (x `mod` 2 == 0) = doit xs doit (x:xs) = (2 * x) : doit xs
since the list is walked twice. (I'm betting someone will respond with a cool one-liner here involving function composition or something else that I can't think of yet :)
Have you tried timing it? I'm not seeing much difference in execution speed between the two functions. Antoine

Am Montag 30 März 2009 06:37:57 schrieb Zachary Turner:
On Sun, Mar 29, 2009 at 6:47 PM, Daniel Fischer
wrote: The &&& operator is pretty sweet, thanks for pointing it out. That's pretty much what I was trying to come up with the mapping and mapping2,
Yep. Pretty good thinking, by the way.
but it's more general and hence more useful.
More general doesn't necessarily imply more useful, specialisation can sometimes be necessary for performance reasons. A big advantage of (&&&) and friends is that many Haskellers know them and won't need to look up the definitions when reading your code, as would be necessary if you use your own differently named variant. So if you come up with with generally useful patterns like (|>), mapping and mapping2, find out whether it's already defined in a library. Try searching for the type in Hoogle, and if it doesn't find it, ask on the list.
The "pipelining" operator I defined should definitely be used with care. For example, it requires the pipelined argument to be the last argument, which is not always the case.
It's the same for ($) and (.). If your pipeline is too complicated to write it with (|>) and a few flips, you should probably write it in a different style anyway.
And I've also found that with it I tend to think about the problem less, and write less efficient code as a result. For example given a list of integers, an easy and very readable way to remove all multiples of 2 from a list, and then double the remaining items could be like this:
let doit x = x |> filter (\y -> y `mod` 2 == 0) |> map (* 2)
as opposed to the more efficient
doit [] = [] doit (x:xs) | (x `mod` 2 == 0) = doit xs doit (x:xs) = (2 * x) : doit xs
since the list is walked twice.
No, thanks to laziness, it's only walked once, the intermediate list won't ever be constructed. If there's any performance difference, it should be minuscule.
(I'm betting someone will respond with a cool one-liner here involving function composition or something else that I can't think of yet :)
list comprehension: doit x = [2*y | y <- x, even y] function composition: doit = map (*2) . filter even doit = filter even >>> map (*2) If you use one of the latter two, be sure to give a type signature, or you'll probably be bitten by the monomorphism restriction.

On Sat, 28 Mar 2009 17:34 -0400, "Brent Yorgey"
Moreover, I've put the 'RealFrac' by looking at ":t floor". What kind of class constraint whould you put for doing eg:
frac x = x - fromInteger (floor (sqrt x) )
since 'floor' takes fractional and 'sqrt' takes RealFrac? Some kind of super-class?
Every instance of RealFrac must also be an instance of Fractional, so just putting RealFrac would be fine. (And I didn't have this memorized, I just started up ghci and typed ':info Fractional' and ':info RealFrac' to see how they are declared.)
Hmm, I gave the wrong types for floor and sqrt above (oops) but your answer should still be valid as a way of looking at things So floor :: (RealFrac a, Integral b) => a -> b sqrt :: (Floating a) => a -> a and looking as you suggest, (Real a, Fractional a) => RealFrac a (Fractional a) => Floating a So in this case the answer is... frac :: (Floating a, RealFrac a) => a -> a frac x = x - fromInteger (floor (sqrt x)) No, common! Please tell me I'm wrong, that there's a simpler way! Clear, qualified answers and a bit of showing off for having something to aspire too. Thank you guys! -- TG cowscanfly@airpost.net -- http://www.fastmail.fm - Does exactly what it says on the tin

Am Sonntag 29 März 2009 19:00:37 schrieb TG:
On Sat, 28 Mar 2009 17:34 -0400, "Brent Yorgey"
wrote:
Moreover, I've put the 'RealFrac' by looking at ":t floor".
What kind of class constraint whould you put for doing eg:
frac x = x - fromInteger (floor (sqrt x) )
since 'floor' takes fractional and 'sqrt' takes RealFrac? Some kind of super-class?
Every instance of RealFrac must also be an instance of Fractional, so just putting RealFrac would be fine. (And I didn't have this memorized, I just started up ghci and typed ':info Fractional' and ':info RealFrac' to see how they are declared.)
Hmm, I gave the wrong types for floor and sqrt above (oops) but your answer should still be valid as a way of looking at things So floor :: (RealFrac a, Integral b) => a -> b sqrt :: (Floating a) => a -> a and looking as you suggest, (Real a, Fractional a) => RealFrac a (Fractional a) => Floating a So in this case the answer is... frac :: (Floating a, RealFrac a) => a -> a frac x = x - fromInteger (floor (sqrt x)) No, common! Please tell me I'm wrong, that there's a simpler way!
Slightly simpler type signature: frac :: RealFloat a => a -> a Prelude> :i RealFloat class (RealFrac a, Floating a) => RealFloat a where floatRadix :: a -> Integer floatDigits :: a -> Int floatRange :: a -> (Int, Int) decodeFloat :: a -> (Integer, Int) encodeFloat :: Integer -> Int -> a exponent :: a -> Int significand :: a -> a scaleFloat :: Int -> a -> a isNaN :: a -> Bool isInfinite :: a -> Bool isDenormalized :: a -> Bool isNegativeZero :: a -> Bool isIEEE :: a -> Bool atan2 :: a -> a -> a -- Defined in GHC.Float instance RealFloat Double -- Defined in GHC.Float instance RealFloat Float -- Defined in GHC.Float
Clear, qualified answers and a bit of showing off for having
something
to aspire too. Thank you guys! -- TG cowscanfly@airpost.net
participants (6)
-
Antoine Latter
-
Brent Yorgey
-
Daniel Fischer
-
John Dorsey
-
TG
-
Zachary Turner