
The operator ($) is often considered an application operator of a lower precedence. Modulo precedence, there seem to be no difference between ($) and `the white space', and so one can quickly get used to treat these operators as being semantically the same. However, they are not the same in all circumstances. I'd like to observe an important case where replacing the application with ($) in a fully-parenthesized expression can lead to a type error.
{-# OPTIONS -fglasgow-exts #-}
module Foo where
data WR = WR (Int -> Int) data W = W (forall a. a->a)
t1 = WR id t2 = W id
We can also write
t1' = WR $ id
However, if we try
t2' = W $ id
we get an error: /tmp/t1.hs:13: Inferred type is less polymorphic than expected Quantified type variable `a' escapes Expected type: (a -> a) -> b Inferred type: (forall a1. a1 -> a1) -> W In the first argument of `($)', namely `W' In the definition of `t2'': t2' = W $ id Incidentally, Hugs -98 gives a quite bizarre error message ERROR "/tmp/t1.hs":13 - Use of W requires at least 1 argument It didn't complain about "WR $ id"... The reasons for that behavior are obvious: the compiler cannot generalize to higher-ranked types when instantiating the type of ($). It makes a difference that the application is a built-in construction, whereas ($) is just a regular function.