[Git][ghc/ghc][master] doc (Foldable): Add examples to Data.Foldable

Marge Bot gitlab at gitlab.haskell.org
Tue Apr 14 11:57:27 UTC 2020



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


Commits:
d0c3b069 by Julien Debon at 2020-04-14T07:57:16-04:00
doc (Foldable): Add examples to Data.Foldable

See #17929

- - - - -


1 changed file:

- libraries/base/Data/Foldable.hs


Changes:

=====================================
libraries/base/Data/Foldable.hs
=====================================
@@ -120,11 +120,44 @@ class Foldable t where
     {-# MINIMAL foldMap | foldr #-}
 
     -- | Combine the elements of a structure using a monoid.
+    --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> fold [[1, 2, 3], [4, 5], [6], []]
+    -- [1,2,3,4,5,6]
+    --
+    -- >>> fold [Sum 1, Sum 3, Sum 5]
+    -- Sum {getSum = 9}
+    --
+    -- Infinite structures never terminate:
+    --
+    -- >>> fold (repeat Nothing)
+    -- * Hangs forever *
     fold :: Monoid m => t m -> m
     fold = foldMap id
 
     -- | Map each element of the structure to a monoid,
     -- and combine the results.
+    --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> foldMap Sum [1, 3, 5]
+    -- Sum {getSum = 9}
+    --
+    -- >>> foldMap Product [1, 3, 5]
+    -- Product {getProduct = 15}
+    --
+    -- >>> foldMap (replicate 3) [1, 2, 3]
+    -- [1,1,1,2,2,2,3,3,3]
+    --
+    -- Infinite structures never terminate:
+    --
+    -- >>> foldMap Sum [1..]
+    -- * Hangs forever *
     foldMap :: Monoid m => (a -> m) -> t a -> m
     {-# INLINE foldMap #-}
     -- This INLINE allows more list functions to fuse. See #9848.
@@ -153,6 +186,49 @@ class Foldable t where
     --
     -- @foldr f z = 'List.foldr' f z . 'toList'@
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> foldr (||) False [False, True, False]
+    -- True
+    --
+    -- >>> foldr (||) False []
+    -- False
+    --
+    -- >>> foldr (\nextChar reversedString -> reversedString ++ [nextChar]) "foo" ['a', 'b', 'c', 'd']
+    -- "foodcba"
+    --
+    -- ===== Infinite structures
+    --
+    -- ⚠️ Applying 'foldr' to infinite structures usually doesn't terminate.
+    --
+    -- It may still terminate in one of the following conditions:
+    --
+    -- * the folding function is short-circuiting
+    -- * the folding function is lazy on its second argument
+    --
+    -- ====== Short-circuiting
+    --
+    -- '(||)' short-circuits on 'True' values, so the following terminates because there is a 'True' value finitely far from the left side:
+    --
+    -- >>> foldr (||) False (True : repeat False)
+    -- True
+    --
+    -- But the following doesn't terminate:
+    --
+    -- >>> foldr (||) False (repeat False ++ [True])
+    -- * Hangs forever *
+    --
+    -- ====== Laziness in the second argument
+    --
+    -- Applying 'foldr' to infinite structures terminates when the folding function is lazy on its second argument:
+    --
+    -- >>> foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1)
+    -- [1,4,7,10,13,16,19,22,25,28,31,34,37,40,43...
+    --
+    -- >>> take 5 $ foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1)
+    -- [1,4,7,10,13]
     foldr :: (a -> b -> b) -> b -> t a -> b
     foldr f z t = appEndo (foldMap (Endo #. f) t) z
 
@@ -189,6 +265,28 @@ class Foldable t where
     --
     -- @foldl f z = 'List.foldl' f z . 'toList'@
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> foldl (+) 42 (Node (Leaf 1) 3 (Node Empty 4 (Leaf 2)))
+    -- 52
+    --
+    -- >>> foldl (+) 42 Empty
+    -- 42
+    --
+    -- >>> foldl (\string nextElement -> nextElement : string) "abcd" (Node (Leaf 'd') 'e' (Node Empty 'f' (Leaf 'g')))
+    -- "gfedabcd"
+    --
+    -- Left-folding infinite structures never terminates:
+    --
+    -- >>> let infiniteNode = Node Empty 1 infiniteNode in foldl (+) 42 infiniteNode
+    -- * Hangs forever *
+    --
+    -- Evaluating the head of the result (when applicable) does not terminate, unlike 'foldr':
+    --
+    -- >>> let infiniteNode = Node Empty 'd' infiniteNode in take 5 (foldl (\string nextElement -> nextElement : string) "abc" infiniteNode)
+    -- * Hangs forever *
     foldl :: (b -> a -> b) -> b -> t a -> b
     foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
     -- There's no point mucking around with coercions here,
@@ -217,7 +315,30 @@ class Foldable t where
     --
     -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
     --
-    -- @'foldr1' f = 'List.foldr1' f . 'toList'@
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> foldr1 (+) [1..4]
+    -- 10
+    --
+    -- >>> foldr1 (+) []
+    -- Exception: Prelude.foldr1: empty list
+    --
+    -- >>> foldr1 (+) Nothing
+    -- *** Exception: foldr1: empty structure
+    --
+    -- >>> foldr1 (-) [1..4]
+    -- -2
+    --
+    -- >>> foldr1 (&&) [True, False, True, True]
+    -- False
+    --
+    -- >>> foldr1 (||) [False, False, True, True]
+    -- True
+    --
+    -- >>> foldr1 (+) [1..]
+    -- * Hangs forever *
     foldr1 :: (a -> a -> a) -> t a -> a
     foldr1 f xs = fromMaybe (errorWithoutStackTrace "foldr1: empty structure")
                     (foldr mf Nothing xs)
@@ -232,6 +353,31 @@ class Foldable t where
     -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
     --
     -- @'foldl1' f = 'List.foldl1' f . 'toList'@
+    --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> foldl1 (+) [1..4]
+    -- 10
+    --
+    -- >>> foldl1 (+) []
+    -- *** Exception: Prelude.foldl1: empty list
+    --
+    -- >>> foldl1 (+) Nothing
+    -- *** Exception: foldl1: empty structure
+    --
+    -- >>> foldl1 (-) [1..4]
+    -- -8
+    --
+    -- >>> foldl1 (&&) [True, False, True, True]
+    -- False
+    --
+    -- >>> foldl1 (||) [False, False, True, True]
+    -- True
+    --
+    -- >>> foldl1 (+) [1..]
+    -- * Hangs forever *
     foldl1 :: (a -> a -> a) -> t a -> a
     foldl1 f xs = fromMaybe (errorWithoutStackTrace "foldl1: empty structure")
                     (foldl mf Nothing xs)
@@ -242,6 +388,27 @@ class Foldable t where
 
     -- | List of elements of a structure, from left to right.
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> toList Nothing
+    -- []
+    --
+    -- >>> toList (Just 42)
+    -- [42]
+    --
+    -- >>> toList (Left "foo")
+    -- []
+    --
+    -- >>> toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))
+    -- [5,17,12,8]
+    --
+    -- For lists, 'toList' is the identity:
+    --
+    -- >>> toList [1, 2, 3]
+    -- [1,2,3]
+    --
     -- @since 4.8.0.0
     toList :: t a -> [a]
     {-# INLINE toList #-}
@@ -251,6 +418,21 @@ class Foldable t where
     -- optimized for structures that are similar to cons-lists, because there
     -- is no general way to do better.
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> null []
+    -- True
+    --
+    -- >>> null [1]
+    -- False
+    --
+    -- 'null' terminates even for infinite structures:
+    --
+    -- >>> null [1..]
+    -- False
+    --
     -- @since 4.8.0.0
     null :: t a -> Bool
     null = foldr (\_ _ -> False) True
@@ -259,12 +441,48 @@ class Foldable t where
     -- default implementation is optimized for structures that are similar to
     -- cons-lists, because there is no general way to do better.
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> length []
+    -- 0
+    --
+    -- >>> length ['a', 'b', 'c']
+    -- 3
+    -- >>> length [1..]
+    -- * Hangs forever *
+    --
     -- @since 4.8.0.0
     length :: t a -> Int
     length = foldl' (\c _ -> c+1) 0
 
     -- | Does the element occur in the structure?
     --
+    -- Note: 'elem' is often used in infix form.
+    --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> 3 `elem` []
+    -- False
+    --
+    -- >>> 3 `elem` [1,2]
+    -- False
+    --
+    -- >>> 3 `elem` [1,2,3,4,5]
+    -- True
+    --
+    -- For infinite structures, 'elem' terminates if the value exists at a
+    -- finite distance from the left side of the structure:
+    --
+    -- >>> 3 `elem` [1..]
+    -- True
+    --
+    -- >>> 3 `elem` ([4..] ++ [3])
+    -- * Hangs forever *
+    --
     -- @since 4.8.0.0
     elem :: Eq a => a -> t a -> Bool
     elem = any . (==)
@@ -273,12 +491,19 @@ class Foldable t where
     --
     -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
     --
-    -- === __Examples__
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
     -- >>> maximum [1..10]
     -- 10
+    --
     -- >>> maximum []
     -- *** Exception: Prelude.maximum: empty list
     --
+    -- >>> maximum Nothing
+    -- *** Exception: maximum: empty structure
+    --
     -- @since 4.8.0.0
     maximum :: forall a . Ord a => t a -> a
     maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") .
@@ -288,12 +513,19 @@ class Foldable t where
     --
     -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty
     --
-    -- === __Examples__
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
     -- >>> minimum [1..10]
     -- 1
+    --
     -- >>> minimum []
     -- *** Exception: Prelude.minimum: empty list
     --
+    -- >>> minimum Nothing
+    -- *** Exception: minimum: empty structure
+    --
     -- @since 4.8.0.0
     minimum :: forall a . Ord a => t a -> a
     minimum = fromMaybe (errorWithoutStackTrace "minimum: empty structure") .
@@ -301,6 +533,25 @@ class Foldable t where
 
     -- | The 'sum' function computes the sum of the numbers of a structure.
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> sum []
+    -- 0
+    --
+    -- >>> sum [42]
+    -- 42
+    --
+    -- >>> sum [1..10]
+    -- 55
+    --
+    -- >>> sum [4.1, 2.0, 1.7]
+    -- 7.8
+    --
+    -- >>> sum [1..]
+    -- * Hangs forever *
+    --
     -- @since 4.8.0.0
     sum :: Num a => t a -> a
     sum = getSum #. foldMap Sum
@@ -308,6 +559,25 @@ class Foldable t where
     -- | The 'product' function computes the product of the numbers of a
     -- structure.
     --
+    -- ==== __Examples__
+    --
+    -- Basic usage:
+    --
+    -- >>> product []
+    -- 1
+    --
+    -- >>> product [42]
+    -- 42
+    --
+    -- >>> product [1..10]
+    -- 3628800
+    --
+    -- >>> product [4.1, 2.0, 1.7]
+    -- 13.939999999999998
+    --
+    -- >>> product [1..]
+    -- * Hangs forever *
+    --
     -- @since 4.8.0.0
     product :: Num a => t a -> a
     product = getProduct #. foldMap Product
@@ -557,6 +827,16 @@ deriving instance Foldable Down
 
 -- | Monadic fold over the elements of a structure,
 -- associating to the right, i.e. from right to left.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> foldrM (\string acc -> print string >> pure (acc + length string)) 42 ["Hello", "world", "!"]
+-- "!"
+-- "world"
+-- "Hello"
+-- 53
 foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
 foldrM f z0 xs = foldl c return xs z0
   -- See Note [List fusion and continuations in 'c']
@@ -565,6 +845,16 @@ foldrM f z0 xs = foldl c return xs z0
 
 -- | Monadic fold over the elements of a structure,
 -- associating to the left, i.e. from left to right.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> foldlM (\acc string -> print string >> pure (acc + length string)) 42 ["Hello", "world", "!"]
+-- "Hello"
+-- "world"
+-- "!"
+-- 53
 foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
 foldlM f z0 xs = foldr c return xs z0
   -- See Note [List fusion and continuations in 'c']
@@ -574,6 +864,15 @@ foldlM f z0 xs = foldr c return xs z0
 -- | Map each element of a structure to an action, evaluate these
 -- actions from left to right, and ignore the results. For a version
 -- that doesn't ignore the results see 'Data.Traversable.traverse'.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> traverse_ print ["Hello", "world", "!"]
+-- "Hello"
+-- "world"
+-- "!"
 traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
 traverse_ f = foldr c (pure ())
   -- See Note [List fusion and continuations in 'c']
@@ -583,6 +882,10 @@ traverse_ f = foldr c (pure ())
 -- | 'for_' is 'traverse_' with its arguments flipped. For a version
 -- that doesn't ignore the results see 'Data.Traversable.for'.
 --
+-- ==== __Examples__
+--
+-- Basic usage:
+--
 -- >>> for_ [1..4] print
 -- 1
 -- 2
@@ -616,6 +919,15 @@ forM_ = flip mapM_
 -- | Evaluate each action in the structure from left to right, and
 -- ignore the results. For a version that doesn't ignore the results
 -- see 'Data.Traversable.sequenceA'.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> sequenceA_ [print "Hello", print "world", print "!"]
+-- "Hello"
+-- "world"
+-- "!"
 sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
 sequenceA_ = foldr c (pure ())
   -- See Note [List fusion and continuations in 'c']
@@ -636,6 +948,10 @@ sequence_ = foldr c (return ())
 
 -- | The sum of a collection of actions, generalizing 'concat'.
 --
+-- ==== __Examples__
+--
+-- Basic usage:
+--
 -- >>> asum [Just "Hello", Nothing, Just "World"]
 -- Just "Hello"
 asum :: (Foldable t, Alternative f) => t (f a) -> f a
@@ -649,12 +965,32 @@ msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
 msum = asum
 
 -- | The concatenation of all the elements of a container of lists.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> concat (Just [1, 2, 3])
+-- [1,2,3]
+--
+-- >>> concat (Node (Leaf [1, 2, 3]) [4, 5] (Node Empty [6] (Leaf [])))
+-- [1,2,3,4,5,6]
 concat :: Foldable t => t [a] -> [a]
 concat xs = build (\c n -> foldr (\x y -> foldr c y x) n xs)
 {-# INLINE concat #-}
 
 -- | Map a function over all the elements of a container and concatenate
 -- the resulting lists.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]]
+-- [1,2,3,10,11,12,100,101,102,1000,1001,1002]
+--
+-- >>> concatMap (take 3) (Node (Leaf [1..]) [10..] Empty)
+-- [1,2,3,10,11,12]
 concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
 concatMap f xs = build (\c n -> foldr (\x b -> foldr c b (f x)) n xs)
 {-# INLINE concatMap #-}
@@ -664,25 +1000,114 @@ concatMap f xs = build (\c n -> foldr (\x b -> foldr c b (f x)) n xs)
 -- | 'and' returns the conjunction of a container of Bools.  For the
 -- result to be 'True', the container must be finite; 'False', however,
 -- results from a 'False' value finitely far from the left end.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> 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 :: Foldable t => t Bool -> Bool
 and = getAll #. foldMap All
 
 -- | 'or' returns the disjunction of a container of Bools.  For the
 -- result to be 'False', the container must be finite; 'True', however,
 -- results from a 'True' value finitely far from the left end.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> 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 :: Foldable t => t Bool -> Bool
 or = getAny #. foldMap Any
 
 -- | Determines whether any element of the structure satisfies the predicate.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> 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 :: Foldable t => (a -> Bool) -> t a -> Bool
 any p = getAny #. foldMap (Any #. p)
 
 -- | Determines whether all elements of the structure satisfy the predicate.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> 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 :: Foldable t => (a -> Bool) -> t a -> Bool
 all p = getAll #. foldMap (All #. p)
 
 -- | The largest element of a non-empty structure with respect to the
 -- given comparison function.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
+-- "Longest"
 
 -- See Note [maximumBy/minimumBy space usage]
 maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
@@ -693,6 +1118,13 @@ maximumBy cmp = foldl1 max'
 
 -- | The least element of a non-empty structure with respect to the
 -- given comparison function.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
+-- "!"
 
 -- See Note [maximumBy/minimumBy space usage]
 minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
@@ -702,12 +1134,47 @@ minimumBy cmp = foldl1 min'
                         _  -> x
 
 -- | 'notElem' is the negation of 'elem'.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> 3 `notElem` []
+-- True
+--
+-- >>> 3 `notElem` [1,2]
+-- True
+--
+-- >>> 3 `notElem` [1,2,3,4,5]
+-- False
+--
+-- For infinite structures, 'notElem' terminates if the value exists at a
+-- finite distance from the left side of the structure:
+--
+-- >>> 3 `notElem` [1..]
+-- False
+--
+-- >>> 3 `notElem` ([4..] ++ [3])
+-- * Hangs forever *
 notElem :: (Foldable t, Eq a) => a -> t a -> Bool
 notElem x = not . elem x
 
 -- | The 'find' function takes a predicate and a structure and returns
 -- the leftmost element of the structure matching the predicate, or
 -- 'Nothing' if there is no such element.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> find (> 42) [0, 5..]
+-- Just 45
+--
+-- >>> find (> 4) (Node (Leaf 3) 17 (Node Empty 12 (Leaf 8)))
+-- Just 17
+--
+-- >>> find (> 12) [1..7]
+-- Nothing
 find :: Foldable t => (a -> Bool) -> t a -> Maybe a
 find p = getFirst . foldMap (\ x -> First (if p x then Just x else Nothing))
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d0c3b0696f1ca809ebd83b5fc2c0b911cde38e77
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/20200414/a2edff9c/attachment-0001.html>


More information about the ghc-commits mailing list