[Haskell-beginners] difference between . and $

A.M. agentm at themactionfaction.com
Sun Oct 30 22:12:23 CET 2011


On Oct 30, 2011, at 1:39 PM, haxl at nym.hush.com wrote:

> Doesn't . and $ do the same thing?  I always get confused about 
> that, like when would I use one over the other.

One good way to answer questions like this for yourself is to jump to the source. By looking at the type in ghci ":t (.)", I found that (.) if defined in GHC.Base. I downloaded the "base" git repo (http://darcs.haskell.org/packages/base.git/) because the online docs for GHC.Base are linked but the link is broken (http://hackage.haskell.org/packages/archive/base/4.4.0.0/doc/html/GHC-Base.html) and found the following:

GHC/Prelude.lhs
{-# INLINE (.) #-}
-- Make sure it has TWO args only on the left, so that it inlines
-- when applied to two functions, even if there is no final argument
(.)    :: (b -> c) -> (a -> b) -> a -> c
(.) f g = \x -> f (g x)

infixr 0  $
...
{-# INLINE ($) #-}
($)                     :: (a -> b) -> a -> b
f $ x                   =  f x

So, we see that (.) returns a lambda of a simple nested function call while ($) is compiled away to perform no extra steps. They are similar in that Haskellers often use them to reduce parentheses but different in their outcomes. In particular, note the difference in types- (.) takes two function arguments while ($) takes only one. 

I am a beginner myself and I often find Haskell modules lightly documented (especially in comparison to more widely-used languages), so I find jumping to the source invaluable.

Cheers,
M


More information about the Beginners mailing list