[Git][ghc/ghc][master] Expand documentation of List & Data.List

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Aug 2 10:06:03 UTC 2023



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


Commits:
ff81d53f by jade at 2023-08-02T06:05:20-04:00
Expand documentation of List & Data.List

This commit aims to improve the documentation and examples
of symbols exported from Data.List

- - - - -


5 changed files:

- libraries/base/Data/List.hs
- libraries/base/Data/OldList.hs
- libraries/base/GHC/Base.hs
- libraries/base/GHC/List.hs
- libraries/ghc-prim/GHC/Types.hs


Changes:

=====================================
libraries/base/Data/List.hs
=====================================
@@ -227,15 +227,21 @@ import GHC.Base ( Bool(..), Eq((==)), otherwise )
 -- the elements of the first list occur, in order, in the second. The
 -- elements do not have to occur consecutively.
 --
--- @'isSubsequenceOf' x y@ is equivalent to @'elem' x ('subsequences' y)@.
+-- @'isSubsequenceOf' x y@ is equivalent to @x \`'elem'\` ('subsequences' y)@.
+--
+-- Note: 'isSubsequenceOf' is often used in infix form.
 --
 -- @since 4.8.0.0
 --
--- >>> isSubsequenceOf "GHC" "The Glorious Haskell Compiler"
+-- ==== __Examples__
+--
+-- >>> "GHC" `isSubsequenceOf` "The Glorious Haskell Compiler"
 -- True
--- >>> isSubsequenceOf ['a','d'..'z'] ['a'..'z']
+--
+-- >>> ['a','d'..'z'] `isSubsequenceOf` ['a'..'z']
 -- True
--- >>> isSubsequenceOf [1..10] [10,9..0]
+--
+-- >>> [1..10] `isSubsequenceOf` [10,9..0]
 -- False
 --
 -- For the result to be 'True', the first list must be finite;
@@ -243,11 +249,12 @@ import GHC.Base ( Bool(..), Eq((==)), otherwise )
 --
 -- >>> [0,2..10] `isSubsequenceOf` [0..]
 -- True
+--
 -- >>> [0..] `isSubsequenceOf` [0,2..10]
 -- False
+--
 -- >>> [0,2..] `isSubsequenceOf` [0..]
 -- * Hangs forever*
---
 isSubsequenceOf :: (Eq a) => [a] -> [a] -> Bool
 isSubsequenceOf []    _                    = True
 isSubsequenceOf _     []                   = False


=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -230,13 +230,9 @@ infix 5 \\ -- comment to fool cpp: https://downloads.haskell.org/~ghc/latest/doc
 -- List functions
 
 -- | The 'dropWhileEnd' function drops the largest suffix of a list
--- in which the given predicate holds for all elements.  For example:
+-- in which the given predicate holds for all elements.
 --
--- >>> dropWhileEnd isSpace "foo\n"
--- "foo"
--- >>> dropWhileEnd isSpace "foo bar"
--- "foo bar"
--- > dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined
+-- ==== __Laziness__
 --
 -- This function is lazy in spine, but strict in elements,
 -- which makes it different from 'reverse' '.' 'dropWhile' @p@ '.' 'reverse',
@@ -244,6 +240,7 @@ infix 5 \\ -- comment to fool cpp: https://downloads.haskell.org/~ghc/latest/doc
 --
 -- >>> take 1 (dropWhileEnd (< 0) (1 : undefined))
 -- [1]
+--
 -- >>> take 1 (reverse $ dropWhile (< 0) $ reverse (1 : undefined))
 -- *** Exception: Prelude.undefined
 --
@@ -251,9 +248,20 @@ infix 5 \\ -- comment to fool cpp: https://downloads.haskell.org/~ghc/latest/doc
 --
 -- >>> last (dropWhileEnd (< 0) [undefined, 1])
 -- *** Exception: Prelude.undefined
+--
 -- >>> last (reverse $ dropWhile (< 0) $ reverse [undefined, 1])
 -- 1
 --
+-- ==== __Examples__
+--
+-- >>> dropWhileEnd isSpace "foo\n"
+-- "foo"
+--
+-- >>> dropWhileEnd isSpace "foo bar"
+-- "foo bar"
+-- >>> dropWhileEnd (> 10) [1..20]
+-- [1,2,3,4,5,6,7,8,9,10]
+--
 -- @since 4.5.0.0
 dropWhileEnd :: (a -> Bool) -> [a] -> [a]
 dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
@@ -262,6 +270,8 @@ dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
 -- prefix from a list. It returns 'Nothing' if the list did not start with the
 -- prefix given, or 'Just' the list after the prefix, if it does.
 --
+-- ===== __Examples__
+--
 -- >>> stripPrefix "foo" "foobar"
 -- Just "bar"
 --
@@ -284,16 +294,29 @@ stripPrefix _ _ = Nothing
 -- or 'Nothing' if there is no such element.
 -- For the result to be 'Nothing', the list must be finite.
 --
+-- ==== __Examples__
+--
 -- >>> elemIndex 4 [0..]
 -- Just 4
+--
+-- >>> elemIndex 'o' "haskell"
+-- Nothing
+--
+-- >>> elemIndex 0 [1..]
+-- * hangs forever *
 elemIndex      :: Eq a => a -> [a] -> Maybe Int
 elemIndex x xs = findIndex (x==) xs -- arity 2 so that we don't get a PAP; #21345
 
 -- | The 'elemIndices' function extends 'elemIndex', by returning the
 -- indices of all elements equal to the query element, in ascending order.
 --
+-- ==== __Examples__
+--
 -- >>> elemIndices 'o' "Hello World"
 -- [4,7]
+--
+-- >>> elemIndices 1 [1, 2, 3, 1, 2, 3]
+-- [0,3]
 elemIndices      :: Eq a => a -> [a] -> [Int]
 elemIndices x xs = findIndices (x==) xs -- arity 2 so that we don't get a PAP; #21345
 
@@ -302,11 +325,16 @@ elemIndices x xs = findIndices (x==) xs -- arity 2 so that we don't get a PAP; #
 -- there is no such element.
 -- For the result to be 'Nothing', the list must be finite.
 --
+-- ==== __Examples__
+--
 -- >>> find (> 4) [1..]
 -- Just 5
 --
 -- >>> find (< 0) [1..10]
 -- Nothing
+--
+-- >>> find ('a' `elem`) ["john", "marcus", "paul"]
+-- Just "marcus"
 find            :: (a -> Bool) -> [a] -> Maybe a
 find p          = listToMaybe . filter p
 
@@ -315,16 +343,32 @@ find p          = listToMaybe . filter p
 -- or 'Nothing' if there is no such element.
 -- For the result to be 'Nothing', the list must be finite.
 --
+-- ==== __Examples__
+--
 -- >>> findIndex isSpace "Hello World!"
 -- Just 5
+--
+-- >>> findIndex odd [0, 2, 4, 6]
+-- Nothing
+--
+-- >>> findIndex even [1..]
+-- Just 1
+--
+-- >>> findIndex odd [0, 2 ..]
+-- * hangs forever *
 findIndex       :: (a -> Bool) -> [a] -> Maybe Int
 findIndex p     = listToMaybe . findIndices p
 
 -- | The 'findIndices' function extends 'findIndex', by returning the
 -- indices of all elements satisfying the predicate, in ascending order.
 --
+-- ==== __Examples__
+--
 -- >>> findIndices (`elem` "aeiou") "Hello World!"
 -- [1,4,7]
+--
+-- >>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"]
+-- [1,3]
 findIndices      :: (a -> Bool) -> [a] -> [Int]
 #if defined(USE_REPORT_PRELUDE)
 findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
@@ -342,8 +386,11 @@ findIndices p ls = build $ \c n ->
 -- | \(\mathcal{O}(\min(m,n))\). The 'isPrefixOf' function takes two lists and
 -- returns 'True' iff the first list is a prefix of the second.
 --
+-- ==== __Examples__
+--
 -- >>> "Hello" `isPrefixOf` "Hello World!"
 -- True
+--
 -- >>> "Hello" `isPrefixOf` "Wello Horld!"
 -- False
 --
@@ -352,10 +399,13 @@ findIndices p ls = build $ \c n ->
 --
 -- >>> [0..] `isPrefixOf` [1..]
 -- False
+--
 -- >>> [0..] `isPrefixOf` [0..99]
 -- False
+--
 -- >>> [0..99] `isPrefixOf` [0..]
 -- True
+--
 -- >>> [0..] `isPrefixOf` [0..]
 -- * Hangs forever *
 --
@@ -372,8 +422,11 @@ isPrefixOf (x:xs) (y:ys)=  x == y && isPrefixOf xs ys
 -- | The 'isSuffixOf' function takes two lists and returns 'True' iff
 -- the first list is a suffix of the second.
 --
+-- ==== __Examples__
+--
 -- >>> "ld!" `isSuffixOf` "Hello World!"
 -- True
+--
 -- >>> "World" `isSuffixOf` "Hello World!"
 -- False
 --
@@ -381,6 +434,7 @@ isPrefixOf (x:xs) (y:ys)=  x == y && isPrefixOf xs ys
 --
 -- >>> [0..] `isSuffixOf` [0..99]
 -- False
+--
 -- >>> [0..99] `isSuffixOf` [0..]
 -- * Hangs forever *
 --
@@ -423,8 +477,11 @@ dropLengthMaybe (_:x') (_:y') = dropLengthMaybe x' y'
 -- iff the first list is contained, wholly and intact,
 -- anywhere within the second.
 --
+-- ==== __Examples__
+--
 -- >>> isInfixOf "Haskell" "I really like Haskell."
 -- True
+--
 -- >>> isInfixOf "Ial" "I really like Haskell."
 -- False
 --
@@ -433,11 +490,12 @@ dropLengthMaybe (_:x') (_:y') = dropLengthMaybe x' y'
 --
 -- >>> [20..50] `isInfixOf` [0..]
 -- True
+--
 -- >>> [0..] `isInfixOf` [20..50]
 -- False
+--
 -- >>> [0..] `isInfixOf` [0..]
 -- * Hangs forever *
---
 isInfixOf               :: (Eq a) => [a] -> [a] -> Bool
 isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
 
@@ -446,8 +504,6 @@ isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
 -- name 'nub' means \`essence\'.) It is a special case of 'nubBy', which allows
 -- the programmer to supply their own equality test.
 --
--- >>> nub [1,2,3,4,3,2,1,2,4,3,5]
--- [1,2,3,4,5]
 --
 -- If there exists @instance Ord a@, it's faster to use `nubOrd` from the `containers` package
 -- ([link to the latest online documentation](https://hackage.haskell.org/package/containers/docs/Data-Containers-ListUtils.html#v:nubOrd)),
@@ -458,17 +514,31 @@ isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
 -- 'map' @Data.List.NonEmpty.@'Data.List.NonEmpty.head' . @Data.List.NonEmpty.@'Data.List.NonEmpty.group' . 'sort',
 -- which takes \(\mathcal{O}(n \log n)\) time, requires @instance Ord a@ and doesn't
 -- preserve the order.
-
 --
+-- ==== __Examples__
+--
+-- >>> nub [1,2,3,4,3,2,1,2,4,3,5]
+-- [1,2,3,4,5]
+--
+-- >>> nub "hello, world!"
+-- "helo, wrd!"
 nub                     :: (Eq a) => [a] -> [a]
 nub                     =  nubBy (==)
 
 -- | The 'nubBy' function behaves just like 'nub', except it uses a
--- user-supplied equality predicate instead of the overloaded '=='
+-- user-supplied equality predicate instead of the overloaded '(==)'
 -- function.
 --
+-- ==== __Examples__
+--
 -- >>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6]
 -- [1,2,6]
+--
+-- >>> nubBy (/=) [2, 7, 1, 8, 2, 8, 1, 8, 2, 8]
+-- [2,2,2]
+--
+-- >>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2]
+-- [1,2,3,5,5]
 nubBy                   :: (a -> a -> Bool) -> [a] -> [a]
 #if defined(USE_REPORT_PRELUDE)
 nubBy eq []             =  []
@@ -496,21 +566,31 @@ elem_by eq y (x:xs)     =  x `eq` y || elem_by eq y xs
 
 
 -- | \(\mathcal{O}(n)\). 'delete' @x@ removes the first occurrence of @x@ from
--- its list argument. For example,
+-- its list argument.
+--
+-- It is a special case of 'deleteBy', which allows the programmer to
+-- supply their own equality test.
+--
+-- ==== __Examples__
 --
 -- >>> delete 'a' "banana"
 -- "bnana"
 --
--- It is a special case of 'deleteBy', which allows the programmer to
--- supply their own equality test.
+-- >>> delete "not" ["haskell", "is", "not", "awesome"]
+-- ["haskell","is","awesome"]
 delete                  :: (Eq a) => a -> [a] -> [a]
 delete                  =  deleteBy (==)
 
 -- | \(\mathcal{O}(n)\). The 'deleteBy' function behaves like 'delete', but
 -- takes a user-supplied equality predicate.
 --
+-- ==== __Examples__
+--
 -- >>> deleteBy (<=) 4 [1..10]
 -- [1,2,3,5,6,7,8,9,10]
+--
+-- >>> deleteBy (/=) 5 [5, 5, 4, 3, 5, 2]
+-- [5,5,3,5,2]
 deleteBy                :: (a -> a -> Bool) -> a -> [a] -> [a]
 deleteBy _  _ []        = []
 deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
@@ -520,26 +600,29 @@ deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
 -- @ys@ in turn (if any) has been removed from @xs at .  Thus
 -- @(xs ++ ys) \\\\ xs == ys at .
 --
--- >>> "Hello World!" \\ "ell W"
--- "Hoorld!"
---
 -- It is a special case of 'deleteFirstsBy', which allows the programmer
 -- to supply their own equality test.
 --
+-- ==== __Examples__
+--
+-- >>> "Hello World!" \\ "ell W"
+-- "Hoorld!"
+--
 -- The second list must be finite, but the first may be infinite.
 --
 -- >>> take 5 ([0..] \\ [2..4])
 -- [0,1,5,6,7]
+--
 -- >>> take 5 ([0..] \\ [2..])
 -- * Hangs forever *
---
 (\\)                    :: (Eq a) => [a] -> [a] -> [a]
 (\\)                    =  foldl (flip delete)
 
 -- | The 'union' function returns the list union of the two lists.
 -- It is a special case of 'unionBy', which allows the programmer to supply
 -- their own equality test.
--- For example,
+--
+-- ==== __Examples__
 --
 -- >>> "dog" `union` "cow"
 -- "dogcw"
@@ -548,7 +631,7 @@ deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
 -- will be used. If the second list contains equal elements, only the first one
 -- will be retained:
 --
--- >>> import Data.Semigroup
+-- >>> import Data.Semigroup(Arg(..))
 -- >>> union [Arg () "dog"] [Arg () "cow"]
 -- [Arg () "dog"]
 -- >>> union [] [Arg () "dog", Arg () "cow"]
@@ -564,19 +647,30 @@ deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
 --
 -- 'union' is productive even if both arguments are infinite.
 --
+-- >>> [0, 2 ..] `union` [1, 3 ..]
+-- [0,2,4,6,8,10,12..
 union                   :: (Eq a) => [a] -> [a] -> [a]
 union                   = unionBy (==)
 
 -- | The 'unionBy' function is the non-overloaded version of 'union'.
 -- Both arguments may be infinite.
 --
+-- ==== __Examples__
+--
+-- >>> unionBy (>) [3, 4, 5] [1, 2, 3, 4, 5, 6]
+-- [3,4,5,4,5,6]
+--
+-- >>> import Data.Semigroup (Arg(..))
+-- >>> unionBy (/=) [Arg () "Saul"] [Arg () "Kim"]
+-- [Arg () "Saul", Arg () "Kim"]
 unionBy                 :: (a -> a -> Bool) -> [a] -> [a] -> [a]
 unionBy eq xs ys        =  xs ++ foldl (flip (deleteBy eq)) (nubBy eq ys) xs
 
 -- | The 'intersect' function takes the list intersection of two lists.
 -- It is a special case of 'intersectBy', which allows the programmer to
 -- supply their own equality test.
--- For example,
+--
+-- ===== __Examples__
 --
 -- >>> [1,2,3,4] `intersect` [2,4,6,8]
 -- [2,4]
@@ -621,19 +715,25 @@ intersectBy _  _  []    =  []
 intersectBy eq xs ys    =  [x | x <- xs, any (eq x) ys]
 
 -- | \(\mathcal{O}(n)\). The 'intersperse' function takes an element and a list
--- and \`intersperses\' that element between the elements of the list. For
--- example,
+-- and \`intersperses\' that element between the elements of the list.
 --
--- >>> intersperse ',' "abcde"
--- "a,b,c,d,e"
+-- ==== __Laziness__
 --
--- 'intersperse' has the following laziness properties:
+-- 'intersperse' has the following properties
 --
 -- >>> take 1 (intersperse undefined ('a' : undefined))
 -- "a"
+--
 -- >>> take 2 (intersperse ',' ('a' : undefined))
 -- "a*** Exception: Prelude.undefined
 --
+-- ==== __Examples__
+--
+-- >>> intersperse ',' "abcde"
+-- "a,b,c,d,e"
+--
+-- >>> intersperse 1 [3, 4, 5]
+-- [3,1,4,1,5]
 intersperse             :: a -> [a] -> [a]
 intersperse _   []      = []
 intersperse sep (x:xs)  = x : prependToAll sep xs
@@ -651,21 +751,39 @@ prependToAll sep (x:xs) = sep : x : prependToAll sep xs
 -- It inserts the list @xs@ in between the lists in @xss@ and concatenates the
 -- result.
 --
--- >>> intercalate ", " ["Lorem", "ipsum", "dolor"]
--- "Lorem, ipsum, dolor"
+-- ==== __Laziness__
 --
--- 'intercalate' has the following laziness properties:
+-- 'intercalate' has the following properties:
 --
 -- >>> take 5 (intercalate undefined ("Lorem" : undefined))
 -- "Lorem"
+--
 -- >>> take 6 (intercalate ", " ("Lorem" : undefined))
 -- "Lorem*** Exception: Prelude.undefined
 --
+-- ==== __Examples__
+--
+-- >>> intercalate ", " ["Lorem", "ipsum", "dolor"]
+-- "Lorem, ipsum, dolor"
+--
+-- >>> intercalate [0, 1] [[2, 3], [4, 5, 6], []]
+-- [2,3,0,1,4,5,6,0,1]
+--
+-- >>> intercalate [1, 2, 3] [[], []]
+-- [1,2,3]
 intercalate :: [a] -> [[a]] -> [a]
 intercalate xs xss = concat (intersperse xs xss)
 
 -- | The 'transpose' function transposes the rows and columns of its argument.
--- For example,
+--
+-- ==== __Laziness__
+--
+-- 'transpose' is lazy in its elements
+--
+-- >>> take 1 (transpose ['a' : undefined, 'b' : undefined])
+-- ["ab"]
+--
+-- ==== __Examples__
 --
 -- >>> transpose [[1,2,3],[4,5,6]]
 -- [[1,4],[2,5],[3,6]]
@@ -679,12 +797,6 @@ intercalate xs xss = concat (intersperse xs xss)
 --
 -- >>> transpose (repeat [])
 -- * Hangs forever *
---
--- 'transpose' is lazy:
---
--- >>> take 1 (transpose ['a' : undefined, 'b' : undefined])
--- ["ab"]
---
 transpose :: [[a]] -> [[a]]
 transpose [] = []
 transpose ([] : xss) = transpose xss
@@ -741,8 +853,16 @@ transpose ((x : xs) : xss) = combine x hds xs tls
 --
 -- > partition p xs == (filter p xs, filter (not . p) xs)
 --
+-- ==== __Examples__
+--
 -- >>> partition (`elem` "aeiou") "Hello World!"
 -- ("eoo","Hll Wrld!")
+--
+-- >>> partition even [1..10]
+-- ([2,4,6,8,10],[1,3,5,7,9])
+--
+-- >>> partition (< 5) [1..10]
+-- ([1,2,3,4],[5,6,7,8,9,10])
 partition               :: (a -> Bool) -> [a] -> ([a],[a])
 {-# INLINE partition #-}
 partition p xs = foldr (select p) ([],[]) xs
@@ -812,12 +932,25 @@ mapAccumR f s (x:xs)    =  (s'', y:ys)
 -- call, the result will also be sorted. It is a special case of 'insertBy',
 -- which allows the programmer to supply their own comparison function.
 --
--- >>> insert 4 [1,2,3,5,6,7]
+-- ==== __Examples__
+--
+-- >>> insert (-1) [1, 2, 3]
+-- [-1,1,2,3]
+--
+-- >>> insert 'd' "abcefg"
+-- "abcdefg"
+--
+-- >>> insert 4 [1, 2, 3, 5, 6, 7]
 -- [1,2,3,4,5,6,7]
 insert :: Ord a => a -> [a] -> [a]
 insert e ls = insertBy (compare) e ls
 
 -- | \(\mathcal{O}(n)\). The non-overloaded version of 'insert'.
+--
+-- ==== __Examples__
+--
+-- >>> insertBy (\x y -> compare (length x) (length y)) [1, 2] [[1], [1, 2, 3], [1, 2, 3, 4]]
+-- [[1],[1,2],[1,2,3],[1,2,3,4]]
 insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
 insertBy _   x [] = [x]
 insertBy cmp x ys@(y:ys')
@@ -830,10 +963,15 @@ insertBy cmp x ys@(y:ys')
 -- and returns the greatest element of the list by the comparison function.
 -- The list must be finite and non-empty.
 --
+-- ==== __Examples__
+--
 -- We can use this to find the longest entry of a list:
 --
 -- >>> maximumBy (\x y -> compare (length x) (length y)) ["Hello", "World", "!", "Longest", "bar"]
 -- "Longest"
+--
+-- >>> minimumBy (\(a, b) (c, d) -> compare (abs (a - b)) (abs (c - d))) [(10, 15), (1, 2), (3, 5)]
+-- (10, 15)
 maximumBy               :: (a -> a -> Ordering) -> [a] -> a
 maximumBy _ []          =  errorWithoutStackTrace "List.maximumBy: empty list"
 maximumBy cmp xs        =  foldl1 maxBy xs
@@ -847,10 +985,15 @@ maximumBy cmp xs        =  foldl1 maxBy xs
 -- and returns the least element of the list by the comparison function.
 -- The list must be finite and non-empty.
 --
+-- ==== __Examples__
+--
 -- We can use this to find the shortest entry of a list:
 --
 -- >>> minimumBy (\x y -> compare (length x) (length y)) ["Hello", "World", "!", "Longest", "bar"]
 -- "!"
+--
+-- >>> minimumBy (\(a, b) (c, d) -> compare (abs (a - b)) (abs (c - d))) [(10, 15), (1, 2), (3, 5)]
+-- (1, 2)
 minimumBy               :: (a -> a -> Ordering) -> [a] -> a
 minimumBy _ []          =  errorWithoutStackTrace "List.minimumBy: empty list"
 minimumBy cmp xs        =  foldl1 minBy xs
@@ -864,6 +1007,8 @@ minimumBy cmp xs        =  foldl1 minBy xs
 -- type which is an instance of 'Num'. It is, however, less efficient than
 -- 'length'.
 --
+-- ==== __Examples__
+--
 -- >>> genericLength [1, 2, 3] :: Int
 -- 3
 -- >>> genericLength [1, 2, 3] :: Float
@@ -1199,18 +1344,24 @@ unzip7          =  foldr (\(a,b,c,d,e,f,g) ~(as,bs,cs,ds,es,fs,gs) ->
 -- returns the first list with the first occurrence of each element of
 -- the second list removed. This is the non-overloaded version of '(\\)'.
 --
+-- > (\\) == deleteFirstsBy (==)
+--
 -- The second list must be finite, but the first may be infinite.
 --
+-- ==== __Examples__
+--
+-- >>> deleteFirstsBy (>) [1..10] [3, 4, 5]
+-- [4,5,6,7,8,9,10]
+--
+-- >>> deleteFirstsBy (/=) [1..10] [1, 3, 5]
+-- [4,5,6,7,8,9,10]
 deleteFirstsBy          :: (a -> a -> Bool) -> [a] -> [a] -> [a]
 deleteFirstsBy eq       =  foldl (flip (deleteBy eq))
 
 -- | The 'group' function takes a list and returns a list of lists such
 -- that the concatenation of the result is equal to the argument.  Moreover,
 -- each sublist in the result is non-empty and all elements are equal
--- to the first one.  For example,
---
--- >>> group "Mississippi"
--- ["M","i","ss","i","ss","i","pp","i"]
+-- to the first one.
 --
 -- 'group' is a special case of 'groupBy', which allows the programmer to supply
 -- their own equality test.
@@ -1218,6 +1369,13 @@ deleteFirstsBy eq       =  foldl (flip (deleteBy eq))
 -- It's often preferable to use @Data.List.NonEmpty.@'Data.List.NonEmpty.group',
 -- which provides type-level guarantees of non-emptiness of inner lists.
 --
+-- ==== __Examples__
+--
+-- >>> group "Mississippi"
+-- ["M","i","ss","i","ss","i","pp","i"]
+--
+-- >>> group [1, 1, 1, 2, 2, 3, 4, 5, 5]
+-- [[1,1,1],[2,2],[3],[4],[5,5]]
 group                   :: Eq a => [a] -> [[a]]
 group                   =  groupBy (==)
 
@@ -1233,16 +1391,28 @@ group                   =  groupBy (==)
 -- It's often preferable to use @Data.List.NonEmpty.@'Data.List.NonEmpty.groupBy',
 -- which provides type-level guarantees of non-emptiness of inner lists.
 --
+-- ==== __Examples__
+--
+-- >>> groupBy (/=) [1, 1, 1, 2, 3, 1, 4, 4, 5]
+-- [[1],[1],[1,2,3],[1,4,4,5]]
+--
+-- >>> groupBy (>) [1, 3, 5, 1, 4, 2, 6, 5, 4]
+-- [[1],[3],[5,1,4,2],[6,5,4]]
+--
+-- >>> groupBy (const not) [True, False, True, False, False, False, True]
+-- [[True,False],[True,False,False,False],[True]]
 groupBy                 :: (a -> a -> Bool) -> [a] -> [[a]]
 groupBy _  []           =  []
 groupBy eq (x:xs)       =  (x:ys) : groupBy eq zs
                            where (ys,zs) = span (eq x) xs
 
 -- | The 'inits' function returns all initial segments of the argument,
--- shortest first.  For example,
+-- shortest first.
 --
--- >>> inits "abc"
--- ["","a","ab","abc"]
+-- 'inits' is semantically equivalent to @'map' 'reverse' . 'scanl' ('flip' (:)) []@,
+-- but under the hood uses a queue to amortize costs of 'reverse'.
+--
+-- ==== __Laziness__
 --
 -- Note that 'inits' has the following strictness property:
 -- @inits (xs ++ _|_) = inits xs ++ _|_@
@@ -1250,9 +1420,18 @@ groupBy eq (x:xs)       =  (x:ys) : groupBy eq zs
 -- In particular,
 -- @inits _|_ = [] : _|_@
 --
--- 'inits' is semantically equivalent to @'map' 'reverse' . 'scanl' ('flip' (:)) []@,
--- but under the hood uses a queue to amortize costs of 'reverse'.
+-- ==== __Examples__
+--
+-- >>> inits "abc"
+-- ["","a","ab","abc"]
+--
+-- >>> inits []
+-- [[]]
+--
+-- inits is productive on infinite lists:
 --
+-- >>> take 5 $ inits [1..]
+-- [[],[1],[1,2],[1,2,3],[1,2,3,4]]
 inits                   :: [a] -> [[a]]
 inits                   = map toListSB . scanl' snocSB emptySB
 {-# NOINLINE inits #-}
@@ -1262,13 +1441,29 @@ inits                   = map toListSB . scanl' snocSB emptySB
 -- loss of sharing if allowed to fuse with a producer.
 
 -- | \(\mathcal{O}(n)\). The 'tails' function returns all final segments of the
--- argument, longest first. For example,
+-- argument, longest first.
 --
--- >>> tails "abc"
--- ["abc","bc","c",""]
+-- ==== __Laziness__
 --
 -- Note that 'tails' has the following strictness property:
 -- @tails _|_ = _|_ : _|_@
+--
+-- >>> tails undefined
+-- [*** Exception: Prelude.undefined
+--
+-- >>> drop 1 (tails [undefined, 1, 2])
+-- [[1, 2], [2], []]
+--
+-- ==== __Examples__
+--
+-- >>> tails "abc"
+-- ["abc","bc","c",""]
+--
+-- >>> tails [1, 2, 3]
+-- [[1,2,3],[2,3],[3],[]]
+--
+-- >>> tails []
+-- [[]]
 tails                   :: [a] -> [[a]]
 {-# INLINABLE tails #-}
 tails lst               =  build (\c n ->
@@ -1279,13 +1474,7 @@ tails lst               =  build (\c n ->
 
 -- | The 'subsequences' function returns the list of all subsequences of the argument.
 --
--- >>> subsequences "abc"
--- ["","a","b","ab","c","ac","bc","abc"]
---
--- This function is productive on infinite inputs:
---
--- >>> take 8 $ subsequences ['a'..]
--- ["","a","b","ab","c","ac","bc","abc"]
+-- ==== __Laziness__
 --
 -- 'subsequences' does not look ahead unless it must:
 --
@@ -1294,6 +1483,15 @@ tails lst               =  build (\c n ->
 -- >>> take 2 (subsequences ('a' : undefined))
 -- ["","a"]
 --
+-- ==== __Examples__
+--
+-- >>> subsequences "abc"
+-- ["","a","b","ab","c","ac","bc","abc"]
+--
+-- This function is productive on infinite inputs:
+--
+-- >>> take 8 $ subsequences ['a'..]
+-- ["","a","b","ab","c","ac","bc","abc"]
 subsequences            :: [a] -> [[a]]
 subsequences xs         =  [] : nonEmptySubsequences xs
 
@@ -1310,23 +1508,32 @@ nonEmptySubsequences (x:xs)  =  [x] : foldr f [] (nonEmptySubsequences xs)
 
 -- | The 'permutations' function returns the list of all permutations of the argument.
 --
--- >>> permutations "abc"
--- ["abc","bac","cba","bca","cab","acb"]
+-- Note that the order of permutations is not lexicographic.
+-- It satisfies the following property:
+--
+-- > map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]
+--
+-- ==== __Laziness__
 --
 -- The 'permutations' function is maximally lazy:
 -- for each @n@, the value of @'permutations' xs@ starts with those permutations
 -- that permute @'take' n xs@ and keep @'drop' n xs at .
 --
--- This function is productive on infinite inputs:
+-- ==== __Examples__
 --
--- >>> take 6 $ map (take 3) $ permutations ['a'..]
+-- >>> permutations "abc"
 -- ["abc","bac","cba","bca","cab","acb"]
 --
--- Note that the order of permutations is not lexicographic.
--- It satisfies the following property:
+-- >>> permutations [1, 2]
+-- [[1,2],[2,1]]
 --
--- > map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]
+-- >>> permutations []
+-- [[]]
 --
+-- This function is productive on infinite inputs:
+--
+-- >>> take 6 $ map (take 3) $ permutations ['a'..]
+-- ["abc","bac","cba","bca","cab","acb"]
 permutations :: [a] -> [[a]]
 -- See https://stackoverflow.com/questions/24484348/what-does-this-list-permutations-implementation-in-haskell-exactly-do/24564307#24564307
 -- for the analysis of this rather cryptic implementation.
@@ -1384,24 +1591,33 @@ permutations xs0 = xs0 : perms xs0 []
 -- Elements are arranged from lowest to highest, keeping duplicates in
 -- the order they appeared in the input.
 --
+-- The argument must be finite.
+--
+-- ==== __Examples__
+--
 -- >>> sort [1,6,4,3,2,5]
 -- [1,2,3,4,5,6]
 --
--- The argument must be finite.
+-- >>> sort "haskell"
+-- "aehklls"
 --
+-- >>> import Data.Semigroup(Arg(..))
+-- >>> sort [Arg ":)" 0, Arg ":D" 0, Arg ":)" 1, Arg ":3" 0, Arg ":D" 1]
+-- [Arg ":)" 0,Arg ":)" 1,Arg ":3" 0,Arg ":D" 0,Arg ":D" 1]
 sort :: (Ord a) => [a] -> [a]
 
 -- | The 'sortBy' function is the non-overloaded version of 'sort'.
 -- The argument must be finite.
 --
--- >>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
--- [(1,"Hello"),(2,"world"),(4,"!")]
---
 -- The supplied comparison relation is supposed to be reflexive and antisymmetric,
 -- otherwise, e. g., for @\_ _ -> GT@, the ordered list simply does not exist.
 -- The relation is also expected to be transitive: if it is not then 'sortBy'
 -- might fail to find an ordered permutation, even if it exists.
 --
+-- ==== __Examples__
+--
+-- >>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
+-- [(1,"Hello"),(2,"world"),(4,"!")]
 sortBy :: (a -> a -> Ordering) -> [a] -> [a]
 
 #if defined(USE_REPORT_PRELUDE)
@@ -1567,10 +1783,15 @@ rqpart cmp x (y:ys) rle rgt r =
 -- Elements are arranged from lowest to highest, keeping duplicates in
 -- the order they appeared in the input.
 --
+-- The argument must be finite.
+--
+-- ==== __Examples__
+--
 -- >>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
 -- [(1,"Hello"),(2,"world"),(4,"!")]
 --
--- The argument must be finite.
+-- >>> sortOn length ["jim", "creed", "pam", "michael", "dwight", "kevin"]
+-- ["jim","pam","creed","kevin","dwight","michael"]
 --
 -- @since 4.8.0.0
 sortOn :: Ord b => (a -> b) -> [a] -> [a]
@@ -1579,9 +1800,17 @@ sortOn f =
 
 -- | Construct a list from a single element.
 --
+-- ==== __Examples__
+--
 -- >>> singleton True
 -- [True]
 --
+-- >>> singleton [1, 2, 3]
+--[[1,2,3]]
+--
+-- >>> singleton 'c'
+-- "c"
+--
 -- @since 4.15.0.0
 --
 singleton :: a -> [a]
@@ -1605,16 +1834,19 @@ singleton x = [x]
 -- > f' (f x y) = Just (x,y)
 -- > f' z       = Nothing
 --
--- A simple use of unfoldr:
---
--- >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
--- [10,9,8,7,6,5,4,3,2,1]
 --
--- Laziness:
+-- ==== __Laziness__
 --
 -- >>> take 1 (unfoldr (\x -> Just (x, undefined)) 'a')
 -- "a"
 --
+-- ==== __Examples__
+--
+-- >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
+-- [10,9,8,7,6,5,4,3,2,1]
+--
+-- >>> take 10 $ unfoldr (\(x, y) -> Just (x, (y, x + y))) (0, 1)
+-- [0,1,1,2,3,5,8,13,21,54]
 
 -- Note [INLINE unfoldr]
 -- ~~~~~~~~~~~~~~~~~~~~~
@@ -1656,30 +1888,35 @@ unfoldr f b0 = build (\c n ->
 -- @\\n@ characters.  The @\\n@ terminator is optional in a final non-empty
 -- line of the argument string.
 --
--- For example:
+-- When the argument string is empty, or ends in a @\\n@ character, it can be
+-- recovered by passing the result of 'lines' to the 'unlines' function.
+-- Otherwise, 'unlines' appends the missing terminating @\\n at .  This makes
+-- @unlines . lines@ /idempotent/:
+--
+-- > (unlines . lines) . (unlines . lines) = (unlines . lines)
+--
+-- ==== __Examples__
 --
 -- >>> lines ""           -- empty input contains no lines
 -- []
+--
 -- >>> lines "\n"         -- single empty line
 -- [""]
+--
 -- >>> lines "one"        -- single unterminated line
 -- ["one"]
+--
 -- >>> lines "one\n"      -- single non-empty line
 -- ["one"]
+--
 -- >>> lines "one\n\n"    -- second line is empty
 -- ["one",""]
+--
 -- >>> lines "one\ntwo"   -- second line is unterminated
 -- ["one","two"]
+--
 -- >>> lines "one\ntwo\n" -- two non-empty lines
 -- ["one","two"]
---
--- When the argument string is empty, or ends in a @\\n@ character, it can be
--- recovered by passing the result of 'lines' to the 'unlines' function.
--- Otherwise, 'unlines' appends the missing terminating @\\n at .  This makes
--- @unlines . lines@ /idempotent/:
---
--- > (unlines . lines) . (unlines . lines) = (unlines . lines)
---
 lines                   :: String -> [String]
 lines ""                =  []
 -- Somehow GHC doesn't detect the selector thunks in the below code,
@@ -1696,6 +1933,8 @@ lines s                 =  cons (case break (== '\n') s of
 -- | Appends a @\\n@ character to each input string, then concatenates the
 -- results. Equivalent to @'foldMap' (\s -> s '++' "\\n")@.
 --
+-- ==== __Examples__
+--
 -- >>> unlines ["Hello", "World", "!"]
 -- "Hello\nWorld\n!\n"
 --
@@ -1717,11 +1956,13 @@ unlines (l:ls) = l ++ '\n' : unlines ls
 -- by white space (as defined by 'isSpace'). This function trims any white spaces
 -- at the beginning and at the end.
 --
+-- ==== __Examples__
+--
 -- >>> words "Lorem ipsum\ndolor"
 -- ["Lorem","ipsum","dolor"]
+--
 -- >>> words " foo bar "
 -- ["foo","bar"]
---
 words                   :: String -> [String]
 {-# NOINLINE [1] words #-}
 words s                 =  case dropWhile {-partain:Char.-}isSpace s of
@@ -1745,9 +1986,6 @@ wordsFB c n = go
 
 -- | 'unwords' joins words with separating spaces (U+0020 SPACE).
 --
--- >>> unwords ["Lorem", "ipsum", "dolor"]
--- "Lorem ipsum dolor"
---
 -- 'unwords' is neither left nor right inverse of 'words':
 --
 -- >>> words (unwords [" "])
@@ -1755,6 +1993,13 @@ wordsFB c n = go
 -- >>> unwords (words "foo\nbar")
 -- "foo bar"
 --
+-- ==== __Examples__
+--
+-- >>> unwords ["Lorem", "ipsum", "dolor"]
+-- "Lorem ipsum dolor"
+--
+-- >>> unwords ["foo", "bar", "", "baz"]
+-- "foo bar  baz"
 unwords                 :: [String] -> String
 #if defined(USE_REPORT_PRELUDE)
 unwords []              =  ""


=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -1452,8 +1452,18 @@ augment g xs = g (:) xs
 -- > map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
 -- > map f [x1, x2, ...] == [f x1, f x2, ...]
 --
+-- this means that @map id == id@
+--
+-- ==== __Examples__
+--
 -- >>> map (+1) [1, 2, 3]
 -- [2,3,4]
+--
+-- >>> map id [1, 2, 3]
+-- [1,2,3]
+--
+-- >>> map (\n -> 3 * n + 1) [1, 2, 3]
+-- [4,7,10]
 map :: (a -> b) -> [a] -> [b]
 {-# NOINLINE [0] map #-}
   -- We want the RULEs "map" and "map/coerce" to fire first.
@@ -1520,21 +1530,33 @@ The rules for map work like this.
 --              append
 ----------------------------------------------
 
--- | Append two lists, i.e.,
+-- | '(++)' appends two lists, i.e.,
 --
 -- > [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn]
 -- > [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
 --
 -- If the first list is not finite, the result is the first list.
 --
+-- ==== __Performance considerations__
+--
 -- This function takes linear time in the number of elements of the
 -- __first__ list. Thus it is better to associate repeated
 -- applications of '(++)' to the right (which is the default behaviour):
 -- @xs ++ (ys ++ zs)@ or simply @xs ++ ys ++ zs@, but not @(xs ++ ys) ++ zs at .
 -- For the same reason 'Data.List.concat' @=@ 'Data.List.foldr' '(++)' @[]@
 -- has linear performance, while 'Data.List.foldl' '(++)' @[]@ is prone
--- to quadratic slowdown.
-
+-- to quadratic slowdown
+--
+-- ==== __Examples__
+--
+-- >>> [1, 2, 3] ++ [4, 5, 6]
+-- [1,2,3,4,5,6]
+--
+-- >>> [] ++ [1, 2, 3]
+-- [1,2,3]
+--
+-- >>> [3, 2, 1] ++ []
+-- [3,2,1]
 (++) :: [a] -> [a] -> [a]
 {-# NOINLINE [2] (++) #-}
   -- Give time for the RULEs for (++) to fire in InitialPhase


=====================================
libraries/base/GHC/List.hs
=====================================
@@ -69,15 +69,16 @@ infix  4 `elem`, `notElem`
 
 -- | \(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.
 --
+-- ===== __Examples__
+--
 -- >>> head [1, 2, 3]
 -- 1
+--
 -- >>> head [1..]
 -- 1
+--
 -- >>> head []
 -- *** Exception: Prelude.head: empty list
---
--- WARNING: This function is partial. You can use case-matching, 'uncons' or
--- 'listToMaybe' instead.
 head                    :: HasCallStack => [a] -> a
 head (x:_)              =  x
 head []                 =  badHead
@@ -105,10 +106,14 @@ badHead = errorEmptyList "head"
 --
 -- @since 4.8.0.0
 --
+-- ==== __Examples__
+--
 -- >>> uncons []
 -- Nothing
+--
 -- >>> uncons [1]
 -- Just (1,[])
+--
 -- >>> uncons [1, 2, 3]
 -- Just (1,[2,3])
 uncons                  :: [a] -> Maybe (a, [a])
@@ -121,28 +126,34 @@ uncons (x:xs)           = Just (x, xs)
 -- * If the list is non-empty, returns @'Just' (xs, x)@,
 -- where @xs@ is the 'init'ial part of the list and @x@ is its 'last' element.
 --
--- @since 4.19.0.0
+--
+-- 'unsnoc' is dual to 'uncons': for a finite list @xs@
+--
+-- > unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
+--
+-- ==== __Examples__
 --
 -- >>> unsnoc []
 -- Nothing
+--
 -- >>> unsnoc [1]
 -- Just ([],1)
+--
 -- >>> unsnoc [1, 2, 3]
 -- Just ([1,2],3)
 --
--- Laziness:
+-- ==== __Laziness__
 --
 -- >>> fst <$> unsnoc [undefined]
 -- Just []
+--
 -- >>> head . fst <$> unsnoc (1 : undefined)
 -- Just *** Exception: Prelude.undefined
+--
 -- >>> head . fst <$> unsnoc (1 : 2 : undefined)
 -- Just 1
 --
--- 'unsnoc' is dual to 'uncons': for a finite list @xs@
---
--- > unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
---
+-- @since 4.19.0.0
 unsnoc :: [a] -> Maybe ([a], a)
 -- The lazy pattern ~(a, b) is important to be productive on infinite lists
 -- and not to be prone to stack overflows.
@@ -153,15 +164,16 @@ unsnoc = foldr (\x -> Just . maybe ([], x) (\(~(a, b)) -> (x : a, b))) Nothing
 -- | \(\mathcal{O}(1)\). Extract the elements after the head of a list, which
 -- must be non-empty.
 --
+-- ==== __Examples__
+--
 -- >>> tail [1, 2, 3]
 -- [2,3]
+--
 -- >>> tail [1]
 -- []
+--
 -- >>> tail []
 -- *** Exception: Prelude.tail: empty list
---
--- WARNING: This function is partial. You can use case-matching or 'uncons'
--- instead.
 tail                    :: HasCallStack => [a] -> [a]
 tail (_:xs)             =  xs
 tail []                 =  errorEmptyList "tail"
@@ -171,14 +183,18 @@ tail []                 =  errorEmptyList "tail"
 -- | \(\mathcal{O}(n)\). Extract the last element of a list, which must be
 -- finite and non-empty.
 --
+-- WARNING: This function is partial. Consider using 'unsnoc' instead.
+--
+-- ==== __Examples__
+--
 -- >>> last [1, 2, 3]
 -- 3
+--
 -- >>> last [1..]
 -- * Hangs forever *
+--
 -- >>> last []
 -- *** Exception: Prelude.last: empty list
---
--- WARNING: This function is partial. Consider using 'unsnoc' instead.
 last                    :: HasCallStack => [a] -> a
 #if defined(USE_REPORT_PRELUDE)
 last [x]                =  x
@@ -199,14 +215,18 @@ lastError = errorEmptyList "last"
 -- | \(\mathcal{O}(n)\). Return all the elements of a list except the last one.
 -- The list must be non-empty.
 --
+-- WARNING: This function is partial. Consider using 'unsnoc' instead.
+--
+-- ==== __Examples__
+--
 -- >>> init [1, 2, 3]
 -- [1,2]
+--
 -- >>> init [1]
 -- []
+--
 -- >>> init []
 -- *** Exception: Prelude.init: empty list
---
--- WARNING: This function is partial. Consider using 'unsnoc' instead.
 init                    :: HasCallStack => [a] -> [a]
 #if defined(USE_REPORT_PRELUDE)
 init [x]                =  []
@@ -270,8 +290,16 @@ idLength = id
 --
 -- > filter p xs = [ x | x <- xs, p x]
 --
+-- ==== __Examples__
+--
 -- >>> filter odd [1, 2, 3]
 -- [1,3]
+--
+-- >>> filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]
+-- ["Hello","World"]
+--
+-- >>> filter (/= 3) [1, 2, 3, 4, 3, 2, 1]
+-- [1,2,4,2,1]
 {-# NOINLINE [1] filter #-}
 filter :: (a -> Bool) -> [a] -> [a]
 filter _pred []    = []
@@ -478,16 +506,23 @@ product                 =  foldl' (*) 1
 --
 -- > last (scanl f z xs) == foldl f z xs
 --
+-- ==== __Examples__
+--
 -- >>> scanl (+) 0 [1..4]
 -- [0,1,3,6,10]
+--
 -- >>> scanl (+) 42 []
 -- [42]
+--
 -- >>> scanl (-) 100 [1..4]
 -- [100,99,97,94,90]
+--
 -- >>> scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
 -- ["foo","afoo","bafoo","cbafoo","dcbafoo"]
+--
 -- >>> take 10 (scanl (+) 0 [1..])
 -- [0,1,3,6,10,15,21,28,36,45]
+--
 -- >>> take 1 (scanl undefined 'a' undefined)
 -- "a"
 
@@ -525,18 +560,26 @@ constScanl = const
 --
 -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
 --
+-- ==== __Examples__
+--
 -- >>> scanl1 (+) [1..4]
 -- [1,3,6,10]
+--
 -- >>> scanl1 (+) []
 -- []
+--
 -- >>> scanl1 (-) [1..4]
 -- [1,-1,-4,-8]
+--
 -- >>> scanl1 (&&) [True, False, True, True]
 -- [True,False,False,False]
+--
 -- >>> scanl1 (||) [False, False, True, True]
 -- [False,False,True,True]
+--
 -- >>> take 10 (scanl1 (+) [1..])
 -- [1,3,6,10,15,21,28,36,45,55]
+--
 -- >>> take 1 (scanl1 undefined ('a' : undefined))
 -- "a"
 scanl1                  :: (a -> a -> a) -> [a] -> [a]
@@ -655,14 +698,20 @@ foldr1 f = go
 --
 -- > head (scanr f z xs) == foldr f z xs.
 --
+-- ==== __Examples__
+--
 -- >>> scanr (+) 0 [1..4]
 -- [10,9,7,4,0]
+--
 -- >>> scanr (+) 42 []
 -- [42]
+--
 -- >>> scanr (-) 100 [1..4]
 -- [98,-97,99,-96,100]
+--
 -- >>> scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
 -- ["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]
+--
 -- >>> force $ scanr (+) 0 [1..]
 -- *** Exception: stack overflow
 {-# NOINLINE [1] scanr #-}
@@ -720,16 +769,23 @@ remove the cause for the chain of evaluations, and all is well.
 -- | \(\mathcal{O}(n)\). 'scanr1' is a variant of 'scanr' that has no starting
 -- value argument.
 --
+-- ==== __Examples__
+--
 -- >>> scanr1 (+) [1..4]
 -- [10,9,7,4]
+--
 -- >>> scanr1 (+) []
 -- []
+--
 -- >>> scanr1 (-) [1..4]
 -- [-2,3,-1,4]
+--
 -- >>> scanr1 (&&) [True, False, True, True]
 -- [False,False,True,True]
+--
 -- >>> scanr1 (||) [True, True, False, False]
 -- [True,True,False,False]
+--
 -- >>> force $ scanr1 (+) [1..]
 -- *** Exception: stack overflow
 scanr1                  :: (a -> a -> a) -> [a] -> [a]
@@ -789,17 +845,27 @@ minimum xs              =  foldl1' min xs
 --
 -- > iterate f x == [x, f x, f (f x), ...]
 --
+-- ==== __Laziness__
+--
 -- Note that 'iterate' is lazy, potentially leading to thunk build-up if
 -- the consumer doesn't force each iterate. See 'iterate'' for a strict
 -- variant of this function.
 --
+-- >>> take 1 $ iterate undefined 42
+-- [42]
+--
+-- ==== __Examples__
+--
 -- >>> take 10 $ iterate not True
 -- [True,False,True,False,True,False,True,False,True,False]
+--
 -- >>> take 10 $ iterate (+3) 42
 -- [42,45,48,51,54,57,60,63,66,69]
--- >>> take 1 $ iterate undefined 42
--- [42]
 --
+-- @iterate id == 'repeat'@:
+--
+-- >>> take 10 $ iterate id 1
+-- [1,1,1,1,1,1,1,1,1,1]
 {-# NOINLINE [1] iterate #-}
 iterate :: (a -> a) -> a -> [a]
 iterate f x =  x : iterate f (f x)
@@ -823,7 +889,6 @@ iterateFB c f x0 = go x0
 --
 -- >>> take 1 $ iterate' undefined 42
 -- *** Exception: Prelude.undefined
---
 {-# NOINLINE [1] iterate' #-}
 iterate' :: (a -> a) -> a -> [a]
 iterate' f x =
@@ -845,8 +910,13 @@ iterate'FB c f x0 = go x0
 
 -- | 'repeat' @x@ is an infinite list, with @x@ the value of every element.
 --
--- >>> repeat 17
--- [17,17,17,17,17,17,17,17,17...
+-- ==== __Examples__
+--
+-- >>> take 10 $ repeat 17
+-- [17,17,17,17,17,17,17,17,17, 17]
+--
+-- >>> repeat undefined
+-- [*** Exception: Prelude.undefined
 repeat :: a -> [a]
 {-# INLINE [0] repeat #-}
 -- The pragma just gives the rules more chance to fire
@@ -867,10 +937,14 @@ repeatFB c x = xs where xs = x `c` xs
 -- It is an instance of the more general 'Data.List.genericReplicate',
 -- in which @n@ may be of any integral type.
 --
+-- ==== __Examples__
+--
 -- >>> replicate 0 True
 -- []
+--
 -- >>> replicate (-1) True
 -- []
+--
 -- >>> replicate 4 True
 -- [True,True,True,True]
 {-# INLINE replicate #-}
@@ -881,15 +955,19 @@ replicate n x           =  take n (repeat x)
 -- the infinite repetition of the original list.  It is the identity
 -- on infinite lists.
 --
+-- ==== __Examples__
+--
 -- >>> cycle []
 -- *** Exception: Prelude.cycle: empty list
+--
 -- >>> take 10 (cycle [42])
 -- [42,42,42,42,42,42,42,42,42,42]
+--
 -- >>> take 10 (cycle [2, 5, 7])
 -- [2,5,7,2,5,7,2,5,7,2]
+--
 -- >>> take 1 (cycle (42 : undefined))
 -- [42]
---
 cycle                   :: HasCallStack => [a] -> [a]
 cycle []                = errorEmptyList "cycle"
 cycle xs                = xs' where xs' = xs ++ xs'
@@ -897,22 +975,27 @@ cycle xs                = xs' where xs' = xs ++ xs'
 -- | 'takeWhile', applied to a predicate @p@ and a list @xs@, returns the
 -- longest prefix (possibly empty) of @xs@ of elements that satisfy @p at .
 --
--- >>> takeWhile (< 3) [1,2,3,4,1,2,3,4]
--- [1,2]
--- >>> takeWhile (< 9) [1,2,3]
--- [1,2,3]
--- >>> takeWhile (< 0) [1,2,3]
--- []
---
--- Laziness:
+-- ==== __Laziness__
 --
 -- >>> takeWhile (const False) undefined
 -- *** Exception: Prelude.undefined
+--
 -- >>> takeWhile (const False) (undefined : undefined)
 -- []
+--
 -- >>> take 1 (takeWhile (const True) (1 : undefined))
 -- [1]
 --
+-- ==== __Examples__
+--
+-- >>> takeWhile (< 3) [1,2,3,4,1,2,3,4]
+-- [1,2]
+--
+-- >>> takeWhile (< 9) [1,2,3]
+-- [1,2,3]
+--
+-- >>> takeWhile (< 0) [1,2,3]
+-- []
 {-# NOINLINE [1] takeWhile #-}
 takeWhile               :: (a -> Bool) -> [a] -> [a]
 takeWhile _ []          =  []
@@ -941,10 +1024,14 @@ takeWhileFB p c n = \x r -> if p x then x `c` r else n
 
 -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs at .
 --
+-- ==== __Examples__
+--
 -- >>> dropWhile (< 3) [1,2,3,4,5,1,2,3]
 -- [3,4,5,1,2,3]
+--
 -- >>> dropWhile (< 9) [1,2,3]
 -- []
+--
 -- >>> dropWhile (< 0) [1,2,3]
 -- [1,2,3]
 dropWhile               :: (a -> Bool) -> [a] -> [a]
@@ -956,28 +1043,35 @@ dropWhile p xs@(x:xs')
 -- | 'take' @n@, applied to a list @xs@, returns the prefix of @xs@
 -- of length @n@, or @xs@ itself if @n >= 'length' xs at .
 --
+-- It is an instance of the more general 'Data.List.genericTake',
+-- in which @n@ may be of any integral type.
+--
+-- ==== __Laziness__
+--
+-- >>> take 0 undefined
+-- []
+-- >>> take 2 (1 : 2 : undefined)
+-- [1,2]
+--
+-- ==== __Examples__
+--
 -- >>> take 5 "Hello World!"
 -- "Hello"
+--
 -- >>> take 3 [1,2,3,4,5]
 -- [1,2,3]
+--
 -- >>> take 3 [1,2]
 -- [1,2]
+--
 -- >>> take 3 []
 -- []
+--
 -- >>> take (-1) [1,2]
 -- []
--- >>> take 0 [1,2]
--- []
 --
--- Laziness:
---
--- >>> take 0 undefined
+-- >>> take 0 [1,2]
 -- []
--- >>> take 1 (1 : undefined)
--- [1]
---
--- It is an instance of the more general 'Data.List.genericTake',
--- in which @n@ may be of any integral type.
 take                   :: Int -> [a] -> [a]
 #if defined(USE_REPORT_PRELUDE)
 take n _      | n <= 0 =  []
@@ -1034,21 +1128,28 @@ takeFB c n x xs
 -- | 'drop' @n xs@ returns the suffix of @xs@
 -- after the first @n@ elements, or @[]@ if @n >= 'length' xs at .
 --
+-- It is an instance of the more general 'Data.List.genericDrop',
+-- in which @n@ may be of any integral type.
+--
+-- ==== __Examples__
+--
 -- >>> drop 6 "Hello World!"
 -- "World!"
+--
 -- >>> drop 3 [1,2,3,4,5]
 -- [4,5]
+--
 -- >>> drop 3 [1,2]
 -- []
+--
 -- >>> drop 3 []
 -- []
+--
 -- >>> drop (-1) [1,2]
 -- [1,2]
+--
 -- >>> drop 0 [1,2]
 -- [1,2]
---
--- It is an instance of the more general 'Data.List.genericDrop',
--- in which @n@ may be of any integral type.
 drop                   :: Int -> [a] -> [a]
 #if defined(USE_REPORT_PRELUDE)
 drop n xs     | n <= 0 =  xs
@@ -1071,34 +1172,45 @@ drop n ls
 -- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of
 -- length @n@ and second element is the remainder of the list:
 --
+-- 'splitAt' is an instance of the more general 'Data.List.genericSplitAt',
+-- in which @n@ may be of any integral type.
+--
+-- ==== __Laziness__
+--
+-- It is equivalent to @('take' n xs, 'drop' n xs)@
+-- unless @n@ is @_|_@:
+-- @splitAt _|_ xs = _|_@, not @(_|_, _|_)@).
+--
+-- The first component of the tuple is produced lazily:
+--
+-- >>> fst (splitAt 0 undefined)
+-- []
+--
+-- >>> take 1 (fst (splitAt 10 (1 : undefined)))
+-- [1]
+--
+-- ==== __Examples__
+--
 -- >>> splitAt 6 "Hello World!"
 -- ("Hello ","World!")
+--
 -- >>> splitAt 3 [1,2,3,4,5]
 -- ([1,2,3],[4,5])
+--
 -- >>> splitAt 1 [1,2,3]
 -- ([1],[2,3])
+--
 -- >>> splitAt 3 [1,2,3]
 -- ([1,2,3],[])
+--
 -- >>> splitAt 4 [1,2,3]
 -- ([1,2,3],[])
+--
 -- >>> splitAt 0 [1,2,3]
 -- ([],[1,2,3])
+--
 -- >>> splitAt (-1) [1,2,3]
 -- ([],[1,2,3])
---
--- It is equivalent to @('take' n xs, 'drop' n xs)@
--- unless @n@ is @_|_@:
--- @splitAt _|_ xs = _|_@, not @(_|_, _|_)@).
---
--- The first component of the tuple is produced lazily:
---
--- >>> fst (splitAt 0 undefined)
--- []
--- >>> take 1 (fst (splitAt 10 (1 : undefined)))
--- [1]
---
--- 'splitAt' is an instance of the more general 'Data.List.genericSplitAt',
--- in which @n@ may be of any integral type.
 splitAt                :: Int -> [a] -> ([a],[a])
 
 #if defined(USE_REPORT_PRELUDE)
@@ -1120,16 +1232,9 @@ splitAt n ls
 -- first element is the longest prefix (possibly empty) of @xs@ of elements that
 -- satisfy @p@ and second element is the remainder of the list:
 --
--- >>> span (< 3) [1,2,3,4,1,2,3,4]
--- ([1,2],[3,4,1,2,3,4])
--- >>> span (< 9) [1,2,3]
--- ([1,2,3],[])
--- >>> span (< 0) [1,2,3]
--- ([],[1,2,3])
---
 -- 'span' @p xs@ is equivalent to @('takeWhile' p xs, 'dropWhile' p xs)@, even if @p@ is @_|_ at .
 --
--- Laziness:
+-- ==== __Laziness__
 --
 -- >>> span undefined []
 -- ([],[])
@@ -1145,6 +1250,16 @@ splitAt n ls
 -- >>> take 10 (fst (span (const True) [1..]))
 -- [1,2,3,4,5,6,7,8,9,10]
 --
+-- ==== __Examples__
+--
+-- >>> span (< 3) [1,2,3,4,1,2,3,4]
+-- ([1,2],[3,4,1,2,3,4])
+--
+-- >>> span (< 9) [1,2,3]
+-- ([1,2,3],[])
+--
+-- >>> span (< 0) [1,2,3]
+-- ([],[1,2,3])
 span                    :: (a -> Bool) -> [a] -> ([a],[a])
 span _ xs@[]            =  (xs, xs)
 span p xs@(x:xs')
@@ -1155,25 +1270,21 @@ span p xs@(x:xs')
 -- first element is longest prefix (possibly empty) of @xs@ of elements that
 -- /do not satisfy/ @p@ and second element is the remainder of the list:
 --
--- >>> break (> 3) [1,2,3,4,1,2,3,4]
--- ([1,2,3],[4,1,2,3,4])
--- >>> break (< 9) [1,2,3]
--- ([],[1,2,3])
--- >>> break (> 9) [1,2,3]
--- ([1,2,3],[])
---
 -- 'break' @p@ is equivalent to @'span' ('not' . p)@
 -- and consequently to @('takeWhile' ('not' . p) xs, 'dropWhile' ('not' . p) xs)@,
 -- even if @p@ is @_|_ at .
 --
--- Laziness:
+-- ==== __Laziness__
 --
 -- >>> break undefined []
 -- ([],[])
+--
 -- >>> fst (break (const True) undefined)
 -- *** Exception: Prelude.undefined
+--
 -- >>> fst (break (const True) (undefined : undefined))
 -- []
+--
 -- >>> take 1 (fst (break (const False) (1 : undefined)))
 -- [1]
 --
@@ -1182,6 +1293,16 @@ span p xs@(x:xs')
 -- >>> take 10 (fst (break (const False) [1..]))
 -- [1,2,3,4,5,6,7,8,9,10]
 --
+-- ==== __Examples__
+--
+-- >>> break (> 3) [1,2,3,4,1,2,3,4]
+-- ([1,2,3],[4,1,2,3,4])
+--
+-- >>> break (< 9) [1,2,3]
+-- ([],[1,2,3])
+--
+-- >>> break (> 9) [1,2,3]
+-- ([1,2,3],[])
 break                   :: (a -> Bool) -> [a] -> ([a],[a])
 #if defined(USE_REPORT_PRELUDE)
 break p                 =  span (not . p)
@@ -1193,15 +1314,30 @@ break p xs@(x:xs')
            | otherwise  =  let (ys,zs) = break p xs' in (x:ys,zs)
 #endif
 
--- | 'reverse' @xs@ returns the elements of @xs@ in reverse order.
+-- | \(\mathcal{O}(n)\). 'reverse' @xs@ returns the elements of @xs@ in reverse order.
 -- @xs@ must be finite.
 --
+-- ==== __Laziness__
+--
+-- 'reverse' is lazy in its elements.
+--
+-- >>> head (reverse [undefined, 1])
+-- 1
+--
+-- >>> reverse (1 : 2 : undefined)
+-- *** Exception: Prelude.undefined
+--
+-- ==== __Examples__
+--
 -- >>> reverse []
 -- []
+--
 -- >>> reverse [42]
 -- [42]
+--
 -- >>> reverse [2,5,7]
 -- [7,5,2]
+--
 -- >>> reverse [1..]
 -- * Hangs forever *
 reverse                 :: [a] -> [a]
@@ -1218,16 +1354,23 @@ reverse l =  rev l []
 -- 'True', the list must be finite; 'False', however, results from a 'False'
 -- value at a finite index of a finite or infinite list.
 --
+-- ==== __Examples__
+--
 -- >>> and []
 -- True
+--
 -- >>> and [True]
 -- True
+--
 -- >>> and [False]
 -- False
+--
 -- >>> and [True, True, False]
 -- False
+--
 -- >>> and (False : repeat True) -- Infinite list [False,True,True,True,True,True,True...
 -- False
+--
 -- >>> and (repeat True)
 -- * Hangs forever *
 and                     :: [Bool] -> Bool
@@ -1248,16 +1391,23 @@ and (x:xs)      =  x && and xs
 -- 'False', the list must be finite; 'True', however, results from a 'True'
 -- value at a finite index of a finite or infinite list.
 --
+-- ==== __Examples__
+--
 -- >>> or []
 -- False
+--
 -- >>> or [True]
 -- True
+--
 -- >>> or [False]
 -- False
+--
 -- >>> or [True, True, False]
 -- True
+--
 -- >>> or (True : repeat False) -- Infinite list [True,False,False,False,False,False,False...
 -- True
+--
 -- >>> or (repeat False)
 -- * Hangs forever *
 or                      :: [Bool] -> Bool
@@ -1280,14 +1430,20 @@ or (x:xs)       =  x || or xs
 -- value for the predicate applied to an element at a finite index of a finite
 -- or infinite list.
 --
+-- ==== __Examples__
+--
 -- >>> any (> 3) []
 -- False
+--
 -- >>> any (> 3) [1,2]
 -- False
+--
 -- >>> any (> 3) [1,2,3,4,5]
 -- True
+--
 -- >>> any (> 3) [1..]
 -- True
+--
 -- >>> any (> 3) [0, -1..]
 -- * Hangs forever *
 any                     :: (a -> Bool) -> [a] -> Bool
@@ -1311,14 +1467,20 @@ any p (x:xs)    = p x || any p xs
 -- value for the predicate applied to an element at a finite index of a finite
 -- or infinite list.
 --
+-- ==== __Examples__
+--
 -- >>> all (> 3) []
 -- True
+--
 -- >>> all (> 3) [1,2]
 -- False
+--
 -- >>> all (> 3) [1,2,3,4,5]
 -- False
+--
 -- >>> all (> 3) [1..]
 -- False
+--
 -- >>> all (> 3) [4..]
 -- * Hangs forever *
 all                     :: (a -> Bool) -> [a] -> Bool
@@ -1341,14 +1503,20 @@ all p (x:xs)    =  p x && all p xs
 -- 'False', the list must be finite; 'True', however, results from an element
 -- equal to @x@ found at a finite index of a finite or infinite list.
 --
+-- ==== __Examples__
+--
 -- >>> 3 `elem` []
 -- False
+--
 -- >>> 3 `elem` [1,2]
 -- False
+--
 -- >>> 3 `elem` [1,2,3,4,5]
 -- True
+--
 -- >>> 3 `elem` [1..]
 -- True
+--
 -- >>> 3 `elem` [4..]
 -- * Hangs forever *
 elem                    :: (Eq a) => a -> [a] -> Bool
@@ -1366,14 +1534,20 @@ elem x (y:ys)   = x==y || elem x ys
 
 -- | 'notElem' is the negation of 'elem'.
 --
+-- ==== __Examples__
+--
 -- >>> 3 `notElem` []
 -- True
+--
 -- >>> 3 `notElem` [1,2]
 -- True
+--
 -- >>> 3 `notElem` [1,2,3,4,5]
 -- False
+--
 -- >>> 3 `notElem` [1..]
 -- False
+--
 -- >>> 3 `notElem` [4..]
 -- * Hangs forever *
 notElem                 :: (Eq a) => a -> [a] -> Bool
@@ -1393,13 +1567,16 @@ notElem x (y:ys)=  x /= y && notElem x ys
 -- list.
 -- For the result to be 'Nothing', the list must be finite.
 --
+-- ==== __Examples__
+--
 -- >>> lookup 2 []
 -- Nothing
+--
 -- >>> lookup 2 [(1, "first")]
 -- Nothing
+--
 -- >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
 -- Just "second"
---
 lookup                  :: (Eq a) => a -> [(a,b)] -> Maybe b
 lookup _key []          =  Nothing
 lookup  key ((x,y):xys)
@@ -1416,10 +1593,16 @@ lookup  key ((x,y):xys)
 --
 -- > concatMap f xs == (concat . map f) xs
 --
+-- ==== __Examples__
+--
 -- >>> concatMap (\i -> [-i,i]) []
 -- []
--- >>> concatMap (\i -> [-i,i]) [1,2,3]
+--
+-- >>> concatMap (\i -> [-i, i]) [1, 2, 3]
 -- [-1,1,-2,2,-3,3]
+--
+-- >>> concatMap ('replicate' 3) [0, 2, 4]
+-- [0,0,0,2,2,2,4,4,4]
 concatMap               :: (a -> [b]) -> [a] -> [b]
 concatMap f             =  foldr ((++) . f) []
 
@@ -1433,12 +1616,16 @@ concatMap f             =  foldr ((++) . f) []
 
 -- | Concatenate a list of lists.
 --
+-- ==== __Examples__
+--
+-- >>> concat [[1,2,3], [4,5], [6], []]
+-- [1,2,3,4,5,6]
+--
 -- >>> concat []
 -- []
+--
 -- >>> concat [[42]]
 -- [42]
--- >>> concat [[1,2,3], [4,5], [6], []]
--- [1,2,3,4,5,6]
 concat :: [[a]] -> [a]
 concat = foldr (++) []
 
@@ -1454,19 +1641,24 @@ concat = foldr (++) []
 -- It is an instance of the more general 'Data.List.genericIndex',
 -- which takes an index of any integral type.
 --
+-- WARNING: This function is partial, and should only be used if you are
+-- sure that the indexing will not fail. Otherwise, use 'Data.List.!?'.
+--
+-- WARNING: This function takes linear time in the index.
+--
+-- ==== __Examples__
+--
 -- >>> ['a', 'b', 'c'] !! 0
 -- 'a'
+--
 -- >>> ['a', 'b', 'c'] !! 2
 -- 'c'
+--
 -- >>> ['a', 'b', 'c'] !! 3
 -- *** Exception: Prelude.!!: index too large
+--
 -- >>> ['a', 'b', 'c'] !! (-1)
 -- *** Exception: Prelude.!!: negative index
---
--- WARNING: This function is partial, and should only be used if you are
--- sure that the indexing will not fail. Otherwise, use 'Data.List.!?'.
---
--- WARNING: This function takes linear time in the index.
 #if defined(USE_REPORT_PRELUDE)
 (!!)                    :: [a] -> Int -> a
 xs     !! n | n < 0 =  errorWithoutStackTrace "Prelude.!!: negative index"
@@ -1498,18 +1690,23 @@ xs !! n
 -- | List index (subscript) operator, starting from 0. Returns 'Nothing'
 -- if the index is out of bounds
 --
+-- This is the total variant of the partial '!!' operator.
+--
+-- WARNING: This function takes linear time in the index.
+--
+-- ==== __Examples__
+--
 -- >>> ['a', 'b', 'c'] !? 0
 -- Just 'a'
+--
 -- >>> ['a', 'b', 'c'] !? 2
 -- Just 'c'
+--
 -- >>> ['a', 'b', 'c'] !? 3
 -- Nothing
+--
 -- >>> ['a', 'b', 'c'] !? (-1)
 -- Nothing
---
--- This is the total variant of the partial '!!' operator.
---
--- WARNING: This function takes linear time in the index.
 (!?) :: [a] -> Int -> Maybe a
 
 {-# INLINABLE (!?) #-}
@@ -1629,31 +1826,36 @@ See the discussion in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10715/
 -- | \(\mathcal{O}(\min(m,n))\). 'zip' takes two lists and returns a list of
 -- corresponding pairs.
 --
--- >>> zip [1, 2] ['a', 'b']
--- [(1,'a'),(2,'b')]
+-- 'zip' is right-lazy:
+--
+-- >>> zip [] undefined
+-- []
+-- >>> zip undefined []
+-- *** Exception: Prelude.undefined
+-- ...
+--
+-- 'zip' is capable of list fusion, but it is restricted to its
+-- first list argument and its resulting list.
+--
+-- ==== __Examples__
+--
+-- >>> zip [1, 2, 3] ['a', 'b', 'c']
+-- [(1,'a'),(2,'b'),(3,'c')]
 --
 -- If one input list is shorter than the other, excess elements of the longer
 -- list are discarded, even if one of the lists is infinite:
 --
 -- >>> zip [1] ['a', 'b']
 -- [(1,'a')]
+--
 -- >>> zip [1, 2] ['a']
 -- [(1,'a')]
+--
 -- >>> zip [] [1..]
 -- []
--- >>> zip [1..] []
--- []
---
--- 'zip' is right-lazy:
 --
--- >>> zip [] undefined
+-- >>> zip [1..] []
 -- []
--- >>> zip undefined []
--- *** Exception: Prelude.undefined
--- ...
---
--- 'zip' is capable of list fusion, but it is restricted to its
--- first list argument and its resulting list.
 {-# NOINLINE [1] zip #-}  -- See Note [Fusion for zipN/zipWithN]
 zip :: [a] -> [b] -> [(a,b)]
 zip []     _bs    = []
@@ -1700,11 +1902,6 @@ zip3FB cons = \a b c r -> (a,b,c) `cons` r
 -- > zipWith (,) xs ys == zip xs ys
 -- > zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
 --
--- For example, @'zipWith' (+)@ is applied to two lists to produce the list of
--- corresponding sums:
---
--- >>> zipWith (+) [1, 2, 3] [4, 5, 6]
--- [5,7,9]
 --
 -- 'zipWith' is right-lazy:
 --
@@ -1714,6 +1911,17 @@ zip3FB cons = \a b c r -> (a,b,c) `cons` r
 --
 -- 'zipWith' is capable of list fusion, but it is restricted to its
 -- first list argument and its resulting list.
+--
+-- ==== __Examples__
+--
+-- @'zipWith' '(+)'@ can be applied to two lists to produce the list of
+-- corresponding sums:
+--
+-- >>> zipWith (+) [1, 2, 3] [4, 5, 6]
+-- [5,7,9]
+--
+-- >>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
+-- ["hello world!","foobar"]
 {-# NOINLINE [1] zipWith #-}  -- See Note [Fusion for zipN/zipWithN]
 zipWith :: (a->b->c) -> [a]->[b]->[c]
 zipWith f = go
@@ -1733,7 +1941,7 @@ zipWithFB c f = \x y r -> (x `f` y) `c` r
 "zipWithList"   [1]  forall f.  foldr2 (zipWithFB (:) f) [] = zipWith f
   #-}
 
--- | The 'zipWith3' function takes a function which combines three
+-- | \(\mathcal{O}(\min(l,m,n))\). The 'zipWith3' function takes a function which combines three
 -- elements, as well as three lists and returns a list of the function applied
 -- to corresponding elements, analogous to 'zipWith'.
 -- It is capable of list fusion, but it is restricted to its
@@ -1741,6 +1949,14 @@ zipWithFB c f = \x y r -> (x `f` y) `c` r
 --
 -- > zipWith3 (,,) xs ys zs == zip3 xs ys zs
 -- > zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
+--
+-- ==== __Examples__
+--
+-- >>> zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"
+-- ["1ax","2by","3cz"]
+--
+-- >>> zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9]
+-- [11,18,27]
 {-# NOINLINE [1] zipWith3 #-}
 zipWith3                :: (a->b->c->d) -> [a]->[b]->[c]->[d]
 zipWith3 z = go
@@ -1760,8 +1976,11 @@ zipWith3FB cons func = \a b c r -> (func a b c) `cons` r
 -- | 'unzip' transforms a list of pairs into a list of first components
 -- and a list of second components.
 --
+-- ==== __Examples__
+--
 -- >>> unzip []
 -- ([],[])
+--
 -- >>> unzip [(1, 'a'), (2, 'b')]
 -- ([1,2],"ab")
 unzip    :: [(a,b)] -> ([a],[b])
@@ -1771,10 +1990,13 @@ unzip    :: [(a,b)] -> ([a],[b])
 unzip    =  foldr (\(a,b) ~(as,bs) -> (a:as,b:bs)) ([],[])
 
 -- | The 'unzip3' function takes a list of triples and returns three
--- lists, analogous to 'unzip'.
+-- lists of the respective components, analogous to 'unzip'.
+--
+-- ==== __Examples__
 --
 -- >>> unzip3 []
 -- ([],[],[])
+--
 -- >>> unzip3 [(1, 'a', True), (2, 'b', False)]
 -- ([1,2],"ab",[True,False])
 unzip3   :: [(a,b,c)] -> ([a],[b],[c])


=====================================
libraries/ghc-prim/GHC/Types.hs
=====================================
@@ -170,19 +170,53 @@ type family Any :: k where { }
 
 -- | The builtin list type, usually written in its non-prefix form @[a]@.
 --
--- ==== __Examples__
+-- In Haskell, lists are one of the most important data types as they are
+-- often used analogous to loops in imperative programming languages.
+-- These lists are singly linked, which makes it unsuited for operations
+-- that require \(\mathcal{O}(1)\) access. Instead, lists are intended to
+-- be traversed.
+--
+-- Lists are constructed recursively using the right-associative cons-operator
+-- @(:) :: a -> [a] -> [a]@, which prepends an element to a list,
+-- and the empty list @[]@.
+--
+-- @
+-- (1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
+-- @
+--
+-- Internally and in memory, all the above are represented like this,
+-- with arrows being pointers to locations in memory.
 --
--- Unless the OverloadedLists extension is enabled, list literals are
--- syntactic sugar for repeated applications of @:@ and @[]@.
+-- > ╭───┬───┬──╮   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭────╮
+-- > │(:)│   │ ─┼──>│(:)│   │ ─┼──>│(:)│   │ ─┼──>│ [] │
+-- > ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰────╯
+-- >       v              v              v
+-- >       1              2              3
+--
+-- As seen above, lists can also be constructed using list literals
+-- of the form @[x_1, x_2, ..., x_n]@
+-- which are syntactic sugar and, unless @-XOverloadedLists@ is enabled,
+-- are translated into uses of @(:)@ and @[]@
+--
+-- Similarly, 'Data.String.String' literals of the form @"I &#x1F49C; hs"@ are translated into
+-- Lists of characters, @[\'I\', \' \', \'&#x1F49C;\', \' \', \'h\', \'s\']@.
+--
+-- ==== __Examples__
 --
--- >>> 1:2:3:4:[] == [1,2,3,4]
--- True
+-- @
+-- >>> [\'H\', \'a\', \'s\', \'k\', \'e\', \'l\', \'l\']
+-- \"Haskell\"
+-- @
 --
--- Similarly, unless the OverloadedStrings extension is enabled, string
--- literals are syntactic sugar for a lists of characters.
+-- @
+-- >>> 1 : [4, 1, 5, 9]
+-- [1,4,1,5,9]
+-- @
 --
--- >>> ['h','e','l','l','o'] == "hello"
--- True
+-- @
+-- >>> [] : [] : []
+-- [[],[]]
+-- @
 --
 -- @since 0.10.0
 --



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ff81d53f6404867c7cdd9dde5bb6bf3776912048
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/20230802/309a1132/attachment-0001.html>


More information about the ghc-commits mailing list