Right-associating infix application operators

In people's responses to my serialization questions, I've seen them using $. I didn't know what it was so I've looked it up. Can someone please confirm my understanding of what it does, please? According to http://en.wikibooks.org/wiki/Haskell/Practical_monads, after the second code sample in the "Return Values" section, it seems to suggest that $ is only used to avoid using so many brackets. Which seems to make sense, but looking at it's definition in Prelude I really can't see why it's useful. Yitz gave me the code; fmap (runGet $ readNames n) $ L.hGetContents h So can I rewrite this without the $ like this? fmap (runGet (readNames n)) (L.hGetContents h) Is there any additional benefit to using $ than just not having to write as many brackets? Thanks, Tom

On Tuesday 06 July 2010 13:00:33, Tom Hobbs wrote:
In people's responses to my serialization questions, I've seen them using $.
I didn't know what it was so I've looked it up. Can someone please confirm my understanding of what it does, please?
According to http://en.wikibooks.org/wiki/Haskell/Practical_monads, after the second code sample in the "Return Values" section, it seems to suggest that $ is only used to avoid using so many brackets. Which
"only" is an exaggeration, make it "mostly". Other common uses are map ($ 3) functionList and zipWith ($) functions arguments it's not necessary, you can get the second from zipWith id functions arguments (even using one keystroke less!) and the first from map (flip id 3) functionList or map (\f -> f 3) functionList As for the zipWith, there's a slight advantage in that ($) stands out more than id, without blacking out the rest. As for the map, well, it takes beginners some time usually to figure out what flip id does (and causes surprise that it's even possible, because flip :: (a -> b -> c) -> b -> a -> c id :: t -> t doesn't make it obvious). And the lambda-expression isn't too beautiful either.
seems to make sense, but looking at it's definition in Prelude I really can't see why it's useful.
Yitz gave me the code;
fmap (runGet $ readNames n) $ L.hGetContents h
So can I rewrite this without the $ like this?
fmap (runGet (readNames n)) (L.hGetContents h)
Yes, that's equivalent. But with deeper nesting, judicious use of ($) can make the code much more readable.
Is there any additional benefit to using $ than just not having to write as many brackets?
See above, it can make things more readable in several ways. But it shouldn't be overused. res = f . g . h . i $ j x is better (IMO) than res = f $ g $ h $ i $ j $ x
Thanks,
Tom

Right, a bit of playing around and I think understand. Maybe.
In your example;
map ($ 3) functionList
I'm assuming that this is Haskel's way of saying "Give the value 3 as an
argument to each function in functionList". Playing in Hugs seems to
suggest that this is the case;
Hugs> map ($ 3) [(4 +), (5 +), (6 +)]
[7,8,9]
That makes sense. The first arg to map is expecting a function, so we give
it a function and a value which just returns the value. I can see why that
works.
Rewriting using "flip id" has me stumped though.
Hugs> map (flip id 3) [(4 +), (5 +), (6 +)]
[7,8,9]
So this is saying,
Actually, I don't know. Working it out in my head I would say "id 3"
returns 3. But "flip 3" causes an error in Hugs, so this code doesn't work
- but clearly it does.
Hugs> :t flip id 3
flip id 3 :: Num a => (a -> b) -> b
Hugs> :t ($ 3)
flip ($) 3 :: Num a => (a -> b) -> b
Is presumably why it works, but I can't work out how to create the type
signature of "flip id 3" from the sigs of flip and id.
Help?
Thanks.
Tom
On Tue, Jul 6, 2010 at 12:19 PM, Daniel Fischer
On Tuesday 06 July 2010 13:00:33, Tom Hobbs wrote:
In people's responses to my serialization questions, I've seen them using $.
I didn't know what it was so I've looked it up. Can someone please confirm my understanding of what it does, please?
According to http://en.wikibooks.org/wiki/Haskell/Practical_monads, after the second code sample in the "Return Values" section, it seems to suggest that $ is only used to avoid using so many brackets. Which
"only" is an exaggeration, make it "mostly".
Other common uses are
map ($ 3) functionList
and
zipWith ($) functions arguments
it's not necessary, you can get the second from
zipWith id functions arguments
(even using one keystroke less!) and the first from
map (flip id 3) functionList
or
map (\f -> f 3) functionList
As for the zipWith, there's a slight advantage in that ($) stands out more than id, without blacking out the rest. As for the map, well, it takes beginners some time usually to figure out what flip id does (and causes surprise that it's even possible, because flip :: (a -> b -> c) -> b -> a -> c id :: t -> t doesn't make it obvious). And the lambda-expression isn't too beautiful either.
seems to make sense, but looking at it's definition in Prelude I really can't see why it's useful.
Yitz gave me the code;
fmap (runGet $ readNames n) $ L.hGetContents h
So can I rewrite this without the $ like this?
fmap (runGet (readNames n)) (L.hGetContents h)
Yes, that's equivalent. But with deeper nesting, judicious use of ($) can make the code much more readable.
Is there any additional benefit to using $ than just not having to write as many brackets?
See above, it can make things more readable in several ways. But it shouldn't be overused.
res = f . g . h . i $ j x
is better (IMO) than
res = f $ g $ h $ i $ j $ x
Thanks,
Tom

On Tuesday 06 July 2010 13:59:08, Tom Hobbs wrote:
Right, a bit of playing around and I think understand. Maybe.
In your example;
map ($ 3) functionList
I'm assuming that this is Haskel's way of saying "Give the value 3 as an argument to each function in functionList".
Right. ($ 3) is a right-section of ($), and like (^3) n ~> n^3, ($ 3) f ~> f $ 3 -- (= f 3).
Playing in Hugs seems to suggest that this is the case;
Hugs> map ($ 3) [(4 +), (5 +), (6 +)] [7,8,9]
That makes sense. The first arg to map is expecting a function, so we give it a function and a value which just returns the value. I can see why that works.
Rewriting using "flip id" has me stumped though.
Hugs> map (flip id 3) [(4 +), (5 +), (6 +)] [7,8,9]
So this is saying,
Actually, I don't know. Working it out in my head I would say "id 3" returns 3. But "flip 3" causes an error in Hugs, so this code doesn't work - but clearly it does.
Wrong parentheses. flip id 3 = (flip id) 3 so (flip id) 3 f ~> (id f) 3 ~> f 3 See, flip :: (a -> b -> c) -> b -> a -> c id :: t -> t to make flip id typecheck, only a subset of all possible types of id can be used here, namely, t must be a function type, t ~ (u -> v) then id :: (u -> v) -> u -> v ---------a--------b----c (remember that (->) associates to the right, so (u -> v) -> (u -> v) is the same as (u -> v) -> u -> v) and flip id :: u -> (u -> v) -> v then flip id 3 :: Num n => (n -> v) -> v
Hugs> :t flip id 3 flip id 3 :: Num a => (a -> b) -> b
You should have tried without the 3, Prelude> :t flip id flip id :: b -> (b -> c) -> c I did mention that it's confusing for beginners, as you saw, it really is. But I hope your thinking about it makes the explanation more effectful than if I had given it right away.
Hugs> :t ($ 3) flip ($) 3 :: Num a => (a -> b) -> b
Is presumably why it works, but I can't work out how to create the type signature of "flip id 3" from the sigs of flip and id.
Help?
Thanks.
Tom
Cheers, Daniel
participants (2)
-
Daniel Fischer
-
Tom Hobbs