Why are `sum` and `product` defined via foldMap' and not foldl'?

Is there a compelling reason for: sum = getSum #. foldMap' Sum product = getProduct #. foldMap' Product rather than: sum = foldl' (+) 0 product = foldl' (*) 1 A quick ghci session with today's GHC head yields: λ> import qualified Data.Foldable as F λ> :set +s λ> F.sum [0..10000000] 50000005000000 (2.98 secs, 1,612,368,368 bytes) λ> F.foldl' (+) 0 [0..10000000] 50000005000000 (0.28 secs, 880,065,112 bytes) The `foldl'` variant looks substantially more efficient (at least for lists), is there some important context in which `foldMap'` is preferable? -- Viktor.

On Wed, Dec 23, 2020 at 01:32:38AM -0500, Viktor Dukhovni wrote:
Is there a compelling reason for:
sum = getSum #. foldMap' Sum product = getProduct #. foldMap' Product
rather than:
sum = foldl' (+) 0 product = foldl' (*) 1 [...] The `foldl'` variant looks substantially more efficient (at least for lists), is there some important context in which `foldMap'` is preferable?
Have you benchmarked with optimisations on? I would not be surprised if a small amount of inlining brings them to the same speed. Tom

Because the related change proposal(s) are never accepted nor implemented. Most recent one is quite recent though. https://mail.haskell.org/pipermail/libraries/2020-October/030862.html - Oleg On 23.12.2020 8.32, Viktor Dukhovni wrote:
Is there a compelling reason for:
sum = getSum #. foldMap' Sum product = getProduct #. foldMap' Product
rather than:
sum = foldl' (+) 0 product = foldl' (*) 1
A quick ghci session with today's GHC head yields:
λ> import qualified Data.Foldable as F λ> :set +s
λ> F.sum [0..10000000] 50000005000000 (2.98 secs, 1,612,368,368 bytes)
λ> F.foldl' (+) 0 [0..10000000] 50000005000000 (0.28 secs, 880,065,112 bytes)
The `foldl'` variant looks substantially more efficient (at least for lists), is there some important context in which `foldMap'` is preferable?

I stand corrected. https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4355 is merged and seems I misread the original e-mail. Foldable should prefer foldMap' (or foldMap) because it offers most opportunities (Monoid mappend is associative). Trees, SnocList work better by default. For lists the implementation could use foldl', because in that special case it makes more sense. These methods (sum, product) are part of Foldable class specifically so they can be overriden. - Oleg On 23.12.2020 12.44, Oleg Grenrus wrote:
Because the related change proposal(s) are never accepted nor implemented.
Most recent one is quite recent though. https://mail.haskell.org/pipermail/libraries/2020-October/030862.html
- Oleg
On 23.12.2020 8.32, Viktor Dukhovni wrote:
Is there a compelling reason for:
sum = getSum #. foldMap' Sum product = getProduct #. foldMap' Product
rather than:
sum = foldl' (+) 0 product = foldl' (*) 1
A quick ghci session with today's GHC head yields:
λ> import qualified Data.Foldable as F λ> :set +s
λ> F.sum [0..10000000] 50000005000000 (2.98 secs, 1,612,368,368 bytes)
λ> F.foldl' (+) 0 [0..10000000] 50000005000000 (0.28 secs, 880,065,112 bytes)
The `foldl'` variant looks substantially more efficient (at least for lists), is there some important context in which `foldMap'` is preferable?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Also, note that the benchmark from the original email: 1) uses ghci, rendering it meaningless as it's not remotely representative of performance of compiled code 2) uses the list instance of Foldable which does *not* use the defaults shown in the original email, but uses explicit definitions. The foldMap' code shown (but not used!) *is* strict, so would, presumably perform comparably to foldl'. Unlike the foldl version of sum that Foldable for lists currently uses. Cheers, Merijn
On 23 Dec 2020, at 13:55, Oleg Grenrus
wrote: I stand corrected. https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4355 is merged
and seems I misread the original e-mail.
Foldable should prefer foldMap' (or foldMap) because it offers most opportunities (Monoid mappend is associative). Trees, SnocList work better by default.
For lists the implementation could use foldl', because in that special case it makes more sense.
These methods (sum, product) are part of Foldable class specifically so they can be overriden.
- Oleg
On 23.12.2020 12.44, Oleg Grenrus wrote:
Because the related change proposal(s) are never accepted nor implemented.
Most recent one is quite recent though. https://mail.haskell.org/pipermail/libraries/2020-October/030862.html
- Oleg
On 23.12.2020 8.32, Viktor Dukhovni wrote:
Is there a compelling reason for:
sum = getSum #. foldMap' Sum product = getProduct #. foldMap' Product
rather than:
sum = foldl' (+) 0 product = foldl' (*) 1
A quick ghci session with today's GHC head yields:
λ> import qualified Data.Foldable as F λ> :set +s
λ> F.sum [0..10000000] 50000005000000 (2.98 secs, 1,612,368,368 bytes)
λ> F.foldl' (+) 0 [0..10000000] 50000005000000 (0.28 secs, 880,065,112 bytes)
The `foldl'` variant looks substantially more efficient (at least for lists), is there some important context in which `foldMap'` is preferable?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Wed, Dec 23, 2020 at 02:08:51PM +0100, Merijn Verstraaten wrote:
Also, note that the benchmark from the original email: 1) uses ghci, rendering it meaningless as it's not remotely representative of performance of compiled code
While indeed List does not use the default definition, when that definition is used for List, the results with optimised compiled code are even more stark. When summing [0..1_000_000_000] using the foldMap'-based definition of `sum`: main :: IO () main = getArgs >>= \case [n] -> go (read n) _ -> go 1_000_000_000 where go :: Int -> IO () go n = print $ getSum #. F.foldMap' Sum $ [0..n] The list elements end up allocated on the heap and I get: $ ./sum1 +RTS -s 500000000500000000 72,000,051,888 bytes allocated in the heap 571,120 bytes copied during GC 44,376 bytes maximum residency (2 sample(s)) 29,352 bytes maximum slop 5 MiB total memory in use (0 MB lost due to fragmentation) INIT time 0.000s ( 0.000s elapsed) MUT time 6.996s ( 6.988s elapsed) GC time 0.036s ( 0.043s elapsed) EXIT time 0.000s ( 0.002s elapsed) Total time 7.033s ( 7.034s elapsed) while with the List instance of foldl': main :: IO () main = getArgs >>= \case [n] -> go (read n) _ -> go 1_000_000_000 where go :: Int -> IO () go n = print $ F.foldl' (+) 0 $ [0..n] the computation avoids heap allocation: $ ./sum2 +RTS -s 500000000500000000 51,816 bytes allocated in the heap 3,320 bytes copied during GC 44,376 bytes maximum residency (1 sample(s)) 25,256 bytes maximum slop 5 MiB total memory in use (0 MB lost due to fragmentation) INIT time 0.000s ( 0.000s elapsed) MUT time 0.346s ( 0.346s elapsed) GC time 0.001s ( 0.001s elapsed) EXIT time 0.000s ( 0.004s elapsed) Total time 0.347s ( 0.351s elapsed)
2) uses the list instance of Foldable which does *not* use the defaults shown in the original email, but uses explicit definitions.
Yes, the "List" instance of `sum` does not use the default definition. That instance shows comparable performance for `sum` and `foldl'` when compiled optimised.
The foldMap' code shown (but not used!) *is* strict, so would, presumably perform comparably to foldl'. Unlike the foldl version of sum that Foldable for lists currently uses.
So my question is basically whether the default is *generally* the more appropriate choice. It clearly is not the more efficient choice for Lists (more precisely, lazily generated iterators). The difference mostly goes away when the data structure in question is already fully realised in memory (as with e.g. strict maps, ...) But I am skeptical that the `foldMap'` defintion is a better default, are there real cases where it is actually better? -- Viktor.

There's no benefit to optimizing default Foldable methods for data types that already have specialized methods.
foldMap' does not care about the nesting of the structure like foldl', so it's a better default choice.
What I worry more about is that getSum . foldl' (\ z x -> z <> Sum x) mempty is compiling to different code than foldl' (+) 0.
—
Sent from my phone with K-9 Mail.
On December 23, 2020 9:52:00 PM UTC, Viktor Dukhovni
On Wed, Dec 23, 2020 at 02:08:51PM +0100, Merijn Verstraaten wrote:
Also, note that the benchmark from the original email: 1) uses ghci, rendering it meaningless as it's not remotely representative of performance of compiled code
While indeed List does not use the default definition, when that definition is used for List, the results with optimised compiled code are even more stark. When summing [0..1_000_000_000] using the foldMap'-based definition of `sum`:
main :: IO () main = getArgs >>= \case [n] -> go (read n) _ -> go 1_000_000_000 where go :: Int -> IO () go n = print $ getSum #. F.foldMap' Sum $ [0..n]
The list elements end up allocated on the heap and I get:
$ ./sum1 +RTS -s 500000000500000000 72,000,051,888 bytes allocated in the heap 571,120 bytes copied during GC 44,376 bytes maximum residency (2 sample(s)) 29,352 bytes maximum slop 5 MiB total memory in use (0 MB lost due to fragmentation)
INIT time 0.000s ( 0.000s elapsed) MUT time 6.996s ( 6.988s elapsed) GC time 0.036s ( 0.043s elapsed) EXIT time 0.000s ( 0.002s elapsed) Total time 7.033s ( 7.034s elapsed)
while with the List instance of foldl':
main :: IO () main = getArgs >>= \case [n] -> go (read n) _ -> go 1_000_000_000 where go :: Int -> IO () go n = print $ F.foldl' (+) 0 $ [0..n]
the computation avoids heap allocation:
$ ./sum2 +RTS -s 500000000500000000 51,816 bytes allocated in the heap 3,320 bytes copied during GC 44,376 bytes maximum residency (1 sample(s)) 25,256 bytes maximum slop 5 MiB total memory in use (0 MB lost due to fragmentation)
INIT time 0.000s ( 0.000s elapsed) MUT time 0.346s ( 0.346s elapsed) GC time 0.001s ( 0.001s elapsed) EXIT time 0.000s ( 0.004s elapsed) Total time 0.347s ( 0.351s elapsed)
2) uses the list instance of Foldable which does *not* use the defaults shown in the original email, but uses explicit definitions.
Yes, the "List" instance of `sum` does not use the default definition. That instance shows comparable performance for `sum` and `foldl'` when compiled optimised.
The foldMap' code shown (but not used!) *is* strict, so would, presumably perform comparably to foldl'. Unlike the foldl version of sum that Foldable for lists currently uses.
So my question is basically whether the default is *generally* the more appropriate choice. It clearly is not the more efficient choice for Lists (more precisely, lazily generated iterators).
The difference mostly goes away when the data structure in question is already fully realised in memory (as with e.g. strict maps, ...)
But I am skeptical that the `foldMap'` defintion is a better default, are there real cases where it is actually better?
-- Viktor. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On mobile, but I don't see how you're compiling? Is it at least with -O1?
On Wed, Dec 23, 2020, 18:26 Keith
There's no benefit to optimizing default Foldable methods for data types that already have specialized methods.
foldMap' does not care about the nesting of the structure like foldl', so it's a better default choice.
What I worry more about is that getSum . foldl' (\ z x -> z <> Sum x) mempty is compiling to different code than foldl' (+) 0. — Sent from my phone with K-9 Mail.
On December 23, 2020 9:52:00 PM UTC, Viktor Dukhovni < ietf-dane@dukhovni.org> wrote:
On Wed, Dec 23, 2020 at 02:08:51PM +0100, Merijn Verstraaten wrote:
Also, note that the benchmark from the original email:
1) uses ghci, rendering it meaningless as it's not remotely representative of performance of compiled code
While indeed List does not use the default definition, when that definition is used for List, the results with optimised compiled code are even more stark. When summing [0..1_000_000_000] using the foldMap'-based definition of `sum`:
main :: IO () main = getArgs >>= \case [n] -> go (read n) _ -> go 1_000_000_000 where go :: Int -> IO () go n = print $ getSum #. F.foldMap' Sum $ [0..n]
The list elements end up allocated on the heap and I get:
$ ./sum1 +RTS -s 500000000500000000 72,000,051,888 bytes allocated in the heap 571,120 bytes copied during GC 44,376 bytes maximum residency (2 sample(s)) 29,352 bytes maximum slop 5 MiB total memory in use (0 MB lost due to fragmentation)
INIT time 0.000s ( 0.000s elapsed) MUT time 6.996s ( 6.988s elapsed) GC time 0.036s ( 0.043s elapsed) EXIT time 0.000s ( 0.002s elapsed) Total time 7.033s ( 7.034s elapsed)
while with the List instance of foldl':
main :: IO () main = getArgs >>= \case [n] -> go (read n) _ -> go 1_000_000_000 where go :: Int -> IO () go n = print $ F.foldl' (+) 0 $ [0..n]
the computation avoids heap allocation:
$ ./sum2 +RTS -s 500000000500000000 51,816 bytes allocated in the heap 3,320 bytes copied during GC 44,376 bytes maximum residency (1 sample(s)) 25,256 bytes maximum slop 5 MiB total memory in use (0 MB lost due to fragmentation)
INIT time 0.000s ( 0.000s elapsed) MUT time 0.346s ( 0.346s elapsed) GC time 0.001s ( 0.001s elapsed) EXIT time 0.000s ( 0.004s elapsed) Total time 0.347s ( 0.351s elapsed)
2) uses the list instance of Foldable which does *not* use the
defaults shown in the original email, but uses explicit definitions.
Yes, the "List" instance of `sum` does not use the default definition. That instance shows comparable performance for `sum` and `foldl'` when compiled optimised.
The foldMap' code shown (but not used!) *is* strict, so would,
presumably perform comparably to foldl'. Unlike the foldl version of sum that Foldable for lists currently uses.
So my question is basically whether the default is *generally* the more appropriate choice. It clearly is not the more efficient choice for Lists (more precisely, lazily generated iterators).
The difference mostly goes away when the data structure in question is already fully realised in memory (as with e.g. strict maps, ...)
But I am skeptical that the `foldMap'` defintion is a better default, are there real cases where it is actually better?
_______________________________________________
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Wed, Dec 23, 2020 at 07:19:37PM -0600, chessai wrote:
On mobile, but I don't see how you're compiling? Is it at least with -O1?
On Wed, Dec 23, 2020, 18:26 Keith
wrote: There's no benefit to optimizing default Foldable methods for data types that already have specialized methods.
foldMap' does not care about the nesting of the structure like foldl', so it's a better default choice.
What I worry more about is that getSum . foldl' (\ z x -> z <> Sum x) mempty is compiling to different code than foldl' (+) 0.
Well, perhaps the same sort of "lifting" concerns that motivated: getSum #. foldMap' Sum in the default definition. With (#.) just ignoring the `getSum` and pretending that foldMap' already returns the correct result. FWIW, my builds were with "-O2". -- Viktor.
participants (6)
-
chessai
-
Keith
-
Merijn Verstraaten
-
Oleg Grenrus
-
Tom Ellis
-
Viktor Dukhovni