Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
GHC
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
Zubin
GHC
Commits
ecf967c2
Commit
ecf967c2
authored
4 years ago
by
Hécate Kleidukos
Committed by
Marge Bot
4 years ago
Browse files
Options
Downloads
Patches
Plain Diff
Rectify the haddock markup surrounding symbols for foldl' and foldMap'
closes #19365
parent
766b11ea
No related branches found
No related tags found
No related merge requests found
Changes
1
Hide whitespace changes
Inline
Side-by-side
Showing
1 changed file
libraries/base/Data/Foldable.hs
+23
-23
23 additions, 23 deletions
libraries/base/Data/Foldable.hs
with
23 additions
and
23 deletions
libraries/base/Data/Foldable.hs
+
23
−
23
View file @
ecf967c2
...
@@ -155,7 +155,7 @@ class Foldable t where
...
@@ -155,7 +155,7 @@ class Foldable t where
-- | Given a structure with elements whose type is a 'Monoid', combine them
-- | Given a structure with elements whose type is a 'Monoid', combine them
-- via the monoid's @('<>')@ operator. This fold is right-associative and
-- via the monoid's @('<>')@ operator. This fold is right-associative and
-- lazy in the accumulator. When you need a strict left-associative fold,
-- lazy in the accumulator. When you need a strict left-associative fold,
-- use
`
foldMap'
`
instead, with 'id' as the map.
-- use
'
foldMap'
'
instead, with 'id' as the map.
--
--
-- ==== __Examples__
-- ==== __Examples__
--
--
...
@@ -185,7 +185,7 @@ class Foldable t where
...
@@ -185,7 +185,7 @@ class Foldable t where
-- | Map each element of the structure into a monoid, and combine the
-- | Map each element of the structure into a monoid, and combine the
-- results with @('<>')@. This fold is right-associative and lazy in the
-- results with @('<>')@. This fold is right-associative and lazy in the
-- accumulator. For strict left-associative folds consider
`
foldMap'
`
-- accumulator. For strict left-associative folds consider
'
foldMap'
'
-- instead.
-- instead.
--
--
-- ==== __Examples__
-- ==== __Examples__
...
@@ -332,7 +332,7 @@ class Foldable t where
...
@@ -332,7 +332,7 @@ class Foldable t where
-- 'foldl' will diverge if given an infinite list.
-- 'foldl' will diverge if given an infinite list.
--
--
-- If you want an efficient strict left-fold, you probably want to use
-- If you want an efficient strict left-fold, you probably want to use
--
`
foldl'
`
instead of 'foldl'. The reason for this is that the latter
--
'
foldl'
'
instead of 'foldl'. The reason for this is that the latter
-- does not force the /inner/ results (e.g. @z \`f\` x1@ in the above
-- does not force the /inner/ results (e.g. @z \`f\` x1@ in the above
-- example) before applying them to the operator (e.g. to @(\`f\` x2)@).
-- example) before applying them to the operator (e.g. to @(\`f\` x2)@).
-- This results in a thunk chain \(\mathcal{O}(n)\) elements long, which
-- This results in a thunk chain \(\mathcal{O}(n)\) elements long, which
...
@@ -346,7 +346,7 @@ class Foldable t where
...
@@ -346,7 +346,7 @@ class Foldable t where
-- ==== __Examples__
-- ==== __Examples__
--
--
-- The first example is a strict fold, which in practice is best performed
-- The first example is a strict fold, which in practice is best performed
-- with
`
foldl'
`
.
-- with
'
foldl'
'
.
--
--
-- >>> foldl (+) 42 [1,2,3,4]
-- >>> foldl (+) 42 [1,2,3,4]
-- 52
-- 52
...
@@ -1481,10 +1481,10 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1481,10 +1481,10 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- with the contributions of all its successors.
-- with the contributions of all its successors.
--
--
-- These two types of folds are typified by the left-associative strict
-- These two types of folds are typified by the left-associative strict
--
`
foldl'
`
and the right-associative lazy `foldr`.
--
'
foldl'
'
and the right-associative lazy `foldr`.
--
--
-- @
-- @
--
`
foldl'
`
:: Foldable t => (b -> a -> b) -> b -> t a -> b
--
'
foldl'
'
:: Foldable t => (b -> a -> b) -> b -> t a -> b
-- `foldr` :: Foldable t => (a -> b -> b) -> b -> t a -> b
-- `foldr` :: Foldable t => (a -> b -> b) -> b -> t a -> b
-- @
-- @
--
--
...
@@ -1508,7 +1508,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1508,7 +1508,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- The third and final argument is a @Foldable@ structure containing elements
-- The third and final argument is a @Foldable@ structure containing elements
-- @(a, b, c, …)@.
-- @(a, b, c, …)@.
--
--
-- * __
`
foldl'
`
__ takes an operator function of the form:
-- * __
'
foldl'
'
__ takes an operator function of the form:
--
--
-- @
-- @
-- f :: b -- accumulated fold of the initial elements
-- f :: b -- accumulated fold of the initial elements
...
@@ -1523,7 +1523,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1523,7 +1523,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- where g element !acc = f acc element
-- where g element !acc = f acc element
-- @
-- @
--
--
-- Since
`
foldl'
`
is strict in the accumulator, this is always
-- Since
'
foldl'
'
is strict in the accumulator, this is always
-- a [strict](#strict) reduction with no opportunity for early return or
-- a [strict](#strict) reduction with no opportunity for early return or
-- intermediate results. The structure must be finite, since no result is
-- intermediate results. The structure must be finite, since no result is
-- returned until the last element is processed. The advantage of
-- returned until the last element is processed. The advantage of
...
@@ -1553,7 +1553,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1553,7 +1553,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- `foldr` is well suited to define both [corecursive](#corec)
-- `foldr` is well suited to define both [corecursive](#corec)
-- and [short-circuit](#short) reductions.
-- and [short-circuit](#short) reductions.
--
--
-- When the operator is always strict in the second argument,
`
foldl'
`
is
-- When the operator is always strict in the second argument,
'
foldl'
'
is
-- generally a better choice than `foldr`. When `foldr` is called with a
-- generally a better choice than `foldr`. When `foldr` is called with a
-- strict operator, evaluation cannot begin until the last element is
-- strict operator, evaluation cannot begin until the last element is
-- reached, by which point a deep stack of pending function applications
-- reached, by which point a deep stack of pending function applications
...
@@ -1620,20 +1620,20 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1620,20 +1620,20 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- processing of the tail of the input structure is generally not only
-- processing of the tail of the input structure is generally not only
-- unnecessary, but also inefficient. Thus, these and similar folds should be
-- unnecessary, but also inefficient. Thus, these and similar folds should be
-- implemented in terms of strict left-associative @Foldable@ methods (typically
-- implemented in terms of strict left-associative @Foldable@ methods (typically
--
`
foldl'
`
) to perform an efficient reduction in constant space.
--
'
foldl'
'
) to perform an efficient reduction in constant space.
--
--
-- Conversely, an implementation of @Foldable@ for a new structure should
-- Conversely, an implementation of @Foldable@ for a new structure should
-- ensure that
`
foldl'
`
actually performs a strict left-associative reduction.
-- ensure that
'
foldl'
'
actually performs a strict left-associative reduction.
--
--
-- The
`
foldMap'
`
method is a special case of
`
foldl'
`
, in which the initial
-- The
'
foldMap'
'
method is a special case of
'
foldl'
'
, in which the initial
-- accumulator is `mempty` and the operator is @mappend . f@, where @f@ maps
-- accumulator is `mempty` and the operator is @mappend . f@, where @f@ maps
-- each input element into the 'Monoid' in question. Therefore,
`
foldMap'
`
is
-- each input element into the 'Monoid' in question. Therefore,
'
foldMap'
'
is
-- an appropriate choice under essentially the same conditions as
`
foldl'
`
, and
-- an appropriate choice under essentially the same conditions as
'
foldl'
'
, and
-- its implementation for a given @Foldable@ structure should also be a strict
-- its implementation for a given @Foldable@ structure should also be a strict
-- left-associative reduction.
-- left-associative reduction.
--
--
-- While the examples below are not necessarily the most optimal definitions of
-- While the examples below are not necessarily the most optimal definitions of
-- the intended functions, they are all cases in which
`
foldMap'
`
is far more
-- the intended functions, they are all cases in which
'
foldMap'
'
is far more
-- appropriate (as well as more efficient) than the lazy `foldMap`.
-- appropriate (as well as more efficient) than the lazy `foldMap`.
--
--
-- > length = getSum . foldMap' (const (Sum 1))
-- > length = getSum . foldMap' (const (Sum 1))
...
@@ -1651,11 +1651,11 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1651,11 +1651,11 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
--
--
-- * Provided the operator is strict in its left argument:
-- * Provided the operator is strict in its left argument:
--
--
-- @
`
foldl'
`
:: Foldable t => (b -> a -> b) -> b -> t a -> b@
-- @
'
foldl'
'
:: Foldable t => (b -> a -> b) -> b -> t a -> b@
--
--
-- * Provided `mappend` is strict in its left argument:
-- * Provided `mappend` is strict in its left argument:
--
--
-- @
`
foldMap'
`
:: (Foldable t, Monoid m) => (a -> m) -> t a -> m@
-- @
'
foldMap'
'
:: (Foldable t, Monoid m) => (a -> m) -> t a -> m@
--
--
-- * Provided the instance is correctly defined:
-- * Provided the instance is correctly defined:
--
--
...
@@ -1782,7 +1782,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1782,7 +1782,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- `all` :: Foldable t => (a -> Bool) -> t a -> Bool
-- `all` :: Foldable t => (a -> Bool) -> t a -> Bool
-- @
-- @
--
--
-- * Many instances of '<|>' (e.g. the 'Maybe' instance) are conditionally
-- * Many instances of
@(
'<|>'
)@
(e.g. the 'Maybe' instance) are conditionally
-- lazy, and use or don't use their second argument depending on the value
-- lazy, and use or don't use their second argument depending on the value
-- of the first. These are used with the folds below, which terminate as
-- of the first. These are used with the folds below, which terminate as
-- early as possible, but otherwise generally keep going. Some instances
-- early as possible, but otherwise generally keep going. Some instances
...
@@ -1795,7 +1795,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1795,7 +1795,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- `msum` :: (Foldable t, MonadPlus m) => t (m a) -> m a
-- `msum` :: (Foldable t, MonadPlus m) => t (m a) -> m a
-- @
-- @
--
--
-- * Likewise, the '*>' operator in some `Applicative` functors, and '>>'
-- * Likewise, the
@(
'*>'
)@
operator in some `Applicative` functors, and
@(
'>>'
)@
-- in some monads are conditionally lazy and can /short-circuit/ a chain of
-- in some monads are conditionally lazy and can /short-circuit/ a chain of
-- computations. The below folds will terminate as early as possible, but
-- computations. The below folds will terminate as early as possible, but
-- even infinite loops can be productive here, when evaluated solely for
-- even infinite loops can be productive here, when evaluated solely for
...
@@ -1868,7 +1868,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1868,7 +1868,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- They do have specialised uses, but are best avoided when in doubt.
-- They do have specialised uses, but are best avoided when in doubt.
--
--
-- @
-- @
--
`
foldr'
`
:: (a -> b -> b) -> b -> t a -> b
--
'
foldr'
'
:: (a -> b -> b) -> b -> t a -> b
-- `foldl` :: (b -> a -> b) -> b -> t a -> b
-- `foldl` :: (b -> a -> b) -> b -> t a -> b
-- `foldl1` :: (a -> a -> a) -> t a -> a
-- `foldl1` :: (a -> a -> a) -> t a -> a
-- `foldrM` :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
-- `foldrM` :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
...
@@ -1879,7 +1879,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1879,7 +1879,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- instances take advantage of efficient right-to-left iteration to perform
-- instances take advantage of efficient right-to-left iteration to perform
-- lazy left folds outside-in from the right-most element.
-- lazy left folds outside-in from the right-most element.
--
--
-- The strict
`
foldr'
`
is the least likely to be useful, structures that
-- The strict
'
foldr'
'
is the least likely to be useful, structures that
-- support efficient sequencing /only/ right-to-left are not at all common.
-- support efficient sequencing /only/ right-to-left are not at all common.
--------------
--------------
...
@@ -1982,7 +1982,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -1982,7 +1982,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
--
--
-- Returning to simpler instances, defined just in terms of `foldr`, it is
-- Returning to simpler instances, defined just in terms of `foldr`, it is
-- somewhat surprising that a fairly efficient /default/ implementation of the
-- somewhat surprising that a fairly efficient /default/ implementation of the
-- strict
`
foldl'
`
is defined in terms of lazy `foldr` when only the latter is
-- strict
'
foldl'
'
is defined in terms of lazy `foldr` when only the latter is
-- explicitly provided by the instance. It may be instructive to take a look
-- explicitly provided by the instance. It may be instructive to take a look
-- at how this works.
-- at how this works.
...
@@ -2067,7 +2067,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
...
@@ -2067,7 +2067,7 @@ https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-- > instance Foldable FRList where
-- > instance Foldable FRList where
-- > foldr f z l = unFR l f z
-- > foldr f z l = unFR l f z
-- > -- With older versions of @base@, also define sum, product, ...
-- > -- With older versions of @base@, also define sum, product, ...
-- > -- to ensure use of the strict
`
foldl'
`
.
-- > -- to ensure use of the strict
'
foldl'
'
.
-- > -- sum = foldl' (+) 0
-- > -- sum = foldl' (+) 0
-- > -- ...
-- > -- ...
--
--
...
...
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment