[Git][ghc/ghc][wip/data-function-documentation] Enhance Documentation of functions exported by Data.Function

Jade (@Jade) gitlab at gitlab.haskell.org
Thu Jan 18 16:43:31 UTC 2024



Jade pushed to branch wip/data-function-documentation at Glasgow Haskell Compiler / GHC


Commits:
35ab882f by Jade at 2024-01-18T17:44:58+01:00
Enhance Documentation of functions exported by Data.Function

This patch aims to improve the documentation of functions exported
in Data.Function

Tracking: #17929
Fixes: #10065

- - - - -


2 changed files:

- libraries/base/src/Data/Function.hs
- libraries/base/src/GHC/Base.hs


Changes:

=====================================
libraries/base/src/Data/Function.hs
=====================================
@@ -39,7 +39,12 @@ infixl 1 &
 -- | @'fix' f@ is the least fixed point of the function @f@,
 -- i.e. the least defined @x@ such that @f x = x at .
 --
--- For example, we can write the factorial function using direct recursion as
+-- When @f@ is strict, this means that because, by the definition of strictness,
+-- @f ⊥ = ⊥@ and such the least defined fixed point of any strict function is @⊥@.
+--
+-- ==== __Examples__
+--
+-- We can write the factorial function using direct recursion as
 --
 -- >>> let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
 -- 120
@@ -53,6 +58,16 @@ infixl 1 &
 -- Instead of making a recursive call, we introduce a dummy parameter @rec@;
 -- when used within 'fix', this parameter then refers to 'fix'’s argument, hence
 -- the recursion is reintroduced.
+--
+-- ==== __Implementation Details__
+--
+-- The current implementation of 'fix' uses structural sharing
+--
+-- @'fix' f = let x = f x in x@
+--
+-- A more straightforward but non-sharing version would look like
+--
+-- @'fix' f = f ('fix' f)@
 fix :: (a -> a) -> a
 fix f = let x = f x in x
 
@@ -60,11 +75,20 @@ fix f = let x = f x in x
 -- unary function @u@ to two arguments @x@ and @y at . From the opposite
 -- perspective, it transforms two inputs and combines the outputs.
 --
--- @((+) \``on`\` f) x y = f x + f y@
+-- @(op \``on`\` f) x y = f x `op` f y@
+--
+-- ==== __Examples__
 --
--- Typical usage: @'Data.List.sortBy' ('Prelude.compare' \`on\` 'Prelude.fst')@.
+-- >>> sortBy (compare `on` length) [[0, 1, 2], [0, 1], [], [0]]
+-- [[],[0],[0,1],[0,1,2]]
 --
--- Algebraic properties:
+-- >>> ((+) `on` length) [1, 2, 3] [-1]
+-- 4
+--
+-- >>> ((,) `on` (*2)) 2 3
+-- (4,6)
+--
+-- ==== __Algebraic properties__
 --
 -- * @(*) \`on\` 'id' = (*) -- (if (*) &#x2209; {&#x22a5;, 'const' &#x22a5;})@
 --
@@ -118,9 +142,14 @@ on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
 -- convenience.  Its precedence is one higher than that of the forward
 -- application operator '$', which allows '&' to be nested in '$'.
 --
+-- ==== __Examples__
+--
 -- >>> 5 & (+1) & show
 -- "6"
 --
+-- >>> sqrt $ [1 / n^2 | n <- [1..1000]] & sum & (*6)
+-- 3.1406380562059946
+--
 -- @since 4.8.0.0
 (&) :: forall r a (b :: TYPE r). a -> (a -> b) -> b
 x & f = f x
@@ -130,7 +159,15 @@ x & f = f x
 --
 -- It is equivalent to @'flip' ('Data.Bool.bool' 'id')@.
 --
--- Algebraic properties:
+-- ==== __Examples__
+--
+-- >>> map (\x -> applyWhen (odd x) (*2) x) [1..10]
+-- [2,2,6,4,10,6,14,8,18,10]
+--
+-- >>> map (\x -> applyWhen (length x > 6) ((++ "...") . take 3) x) ["Hi!", "This is amazing", "Hope you're doing well today!", ":D"]
+-- ["Hi!","Thi...","Hop...",":D"]
+--
+-- ==== __Algebraic properties__
 --
 -- * @applyWhen 'True' = 'id'@
 --


=====================================
libraries/base/src/GHC/Base.hs
=====================================
@@ -1703,6 +1703,20 @@ maxInt  = I# 0x7FFFFFFFFFFFFFFF#
 -- | Identity function.
 --
 -- > id x = x
+--
+-- This function might seem useless at first glance, but it can be very useful
+-- in a higher order context.
+--
+-- ==== __Examples__
+--
+-- >>> length $ filter id [True, True, False, True]
+-- 3
+--
+-- >>> Just (Just 3) >>= id
+-- Just 3
+--
+-- >>> foldl (flip id) 0 [(+2), (*5), (^3)]
+-- 1000
 id                      :: a -> a
 id x                    =  x
 
@@ -1736,6 +1750,13 @@ breakpointCond _ r = r
 data Opaque = forall a. O a
 -- | @const x y@ always evaluates to @x@, ignoring its second argument.
 --
+-- > const x = \_ -> x
+--
+-- This function might seem useless at first glance, but it can be very useful
+-- in a higher order context.
+--
+-- ==== __Examples__
+--
 -- >>> const 42 "hello"
 -- 42
 --
@@ -1744,7 +1765,17 @@ data Opaque = forall a. O a
 const                   :: a -> b -> a
 const x _               =  x
 
--- | Function composition.
+-- | Right to left function composition.
+--
+-- prop> (f . g) x = f (g x)
+--
+-- ==== __Examples__
+--
+-- >>> map ((*2) . length) [[], [0, 1, 2], [0]]
+-- [0,6,2]
+--
+-- >>> even . sum . map (+1) $ [0,1,2,3,4]
+-- False
 {-# 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
@@ -1753,8 +1784,15 @@ const x _               =  x
 
 -- | @'flip' f@ takes its (first) two arguments in the reverse order of @f at .
 --
+-- prop> flip f x y = f y x
+--
+-- ==== __Examples__
+--
 -- >>> flip (++) "hello" "world"
 -- "worldhello"
+--
+-- >>> let (.>) = flip (.) in (+1) .> show $ 5
+-- "6"
 flip                    :: (a -> b -> c) -> b -> a -> c
 flip f x y              =  f y x
 
@@ -1766,9 +1804,9 @@ 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.
 
-{- | @($)@ is the __function application__ operator.
+{- | @'($)'@ 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:
+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
@@ -1791,7 +1829,7 @@ expr = min 5 $ 1 + 5
 expr = (min 5) (1 + 5)
 @
 
-=== Uses
+==== __Examples__
 
 A common use cases of @($)@ is to avoid parentheses in complex expressions.
 
@@ -1820,7 +1858,7 @@ applyFive = map ($ 5) [(+1), (2^)]
 >>> [6, 32]
 @
 
-=== Technical Remark (Representation Polymorphism)
+==== __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:
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35ab882f08fa1d52b46faf86e938d5ab5cfdac21

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35ab882f08fa1d52b46faf86e938d5ab5cfdac21
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/20240118/fc38a5be/attachment-0001.html>


More information about the ghc-commits mailing list