[Git][ghc/ghc][master] 3 commits: Improve documentation for ($) (#22963)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Apr 7 22:28:04 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
cbbfb283 by Alex Dixon at 2023-04-07T18:27:45-04:00
Improve documentation for ($) (#22963)

- - - - -
5193c2b0 by Alex Dixon at 2023-04-07T18:27:45-04:00
Remove trailing whitespace from ($) commentary

- - - - -
b384523b by Sebastian Graf at 2023-04-07T18:27:45-04:00
Adjust wording wrt representation polymorphism of ($)
- - - - -


1 changed file:

- libraries/base/GHC/Base.hs


Changes:

=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -1606,18 +1606,69 @@ flip f x y              =  f y x
 -- (\x -> undefined x) `seq` () and thus would just evaluate to (), but now
 -- it is equivalent to undefined `seq` () which diverges.
 
--- | Application operator.  This operator is redundant, since ordinary
--- application @(f x)@ means the same as @(f '$' x)@. However, '$' has
--- low, right-associative binding precedence, so it sometimes allows
--- parentheses to be omitted; for example:
---
--- > f $ g $ h x  =  f (g (h x))
---
--- It is also useful in higher-order situations, such as @'map' ('$' 0) xs@,
--- or @'Data.List.zipWith' ('$') fs xs at .
---
--- Note that @('$')@ is representation-polymorphic, so that
--- @foo '$' 4#@ where @foo :: Int# -> Int#@ is well-typed.
+{- | @($)@ is the __function application__ operator.
+
+Applying @($)@ to a function @f@ and an argument @x@ gives the same result as applying @f@ to @x@ directly. The definition is akin to this:
+
+@
+($) :: (a -> b) -> a -> b
+($) f x = f x
+@
+
+On the face of it, this may appear pointless! But it's actually one of the most useful and important operators in Haskell.
+
+The order of operations is very different between @($)@ and normal function application. Normal function application has precedence 10 - higher than any operator - and associates to the left. So these two definitions are equivalent:
+
+@
+expr = min 5 1 + 5
+expr = ((min 5) 1) + 5
+@
+
+@($)@ has precedence 0 (the lowest) and associates to the right, so these are equivalent:
+
+@
+expr = min 5 $ 1 + 5
+expr = (min 5) (1 + 5)
+@
+
+=== Uses
+
+A common use cases of @($)@ is to avoid parentheses in complex expressions.
+
+For example, instead of using nested parentheses in the following
+ Haskell function:
+
+@
+-- | Sum numbers in a string: strSum "100  5 -7" == 98
+strSum :: 'String' -> 'Int'
+strSum s = 'sum' ('Data.Maybe.mapMaybe' 'Text.Read.readMaybe' ('words' s))
+@
+
+we can deploy the function application operator:
+
+@
+-- | Sum numbers in a string: strSum "100  5 -7" == 98
+strSum :: 'String' -> 'Int'
+strSum s = 'sum' '$' 'Data.Maybe.mapMaybe' 'Text.Read.readMaybe' '$' 'words' s
+@
+
+@($)@ is also used as a section (a partially applied operator), in order to indicate that we wish to apply some yet-unspecified function to a given value. For example, to apply the argument @5@ to a list of functions:
+
+@
+applyFive :: [Int]
+applyFive = map ($ 5) [(+1), (2^)]
+>>> [6, 32]
+@
+
+=== Technical Remark (Representation Polymorphism)
+
+@($)@ is fully representation-polymorphic. This allows it to also be used with arguments of unlifted and even unboxed kinds, such as unboxed integers:
+
+@
+fastMod :: Int -> Int -> Int
+fastMod (I# x) (I# m) = I# $ remInt# x m
+@
+-}
 {-# INLINE ($) #-}
 ($) :: forall repa repb (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b
 ($) f = f



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c990e13c36b7be7d3bd3af050ad49182a028f21...b384523bab0650ba1e6b09f3c7aa64a92a90fe3b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c990e13c36b7be7d3bd3af050ad49182a028f21...b384523bab0650ba1e6b09f3c7aa64a92a90fe3b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230407/ae4bc967/attachment-0001.html>


More information about the ghc-commits mailing list