Proposal: Strict variant of foldMap

Andrew Martin andrew.thaddeus at gmail.com
Fri Jun 29 00:11:30 UTC 2018


I don't see any reason to not do this. Someone just needs to put a
differential on phabricator, adding foldMap, a default implementation, and
documentation of it. It would be maybe 6 lines total. The default
implementation of foldMap' would use foldl' and that would be optimal for
everything in base.

On Thu, Jun 28, 2018 at 6:38 PM, Simon Jakobi via Libraries <
libraries at haskell.org> wrote:

> Is there any chance that foldMap' might still make it into base-4.12?
> Am Sa., 9. Juni 2018 um 10:23 Uhr schrieb Edward Kmett <ekmett at gmail.com>:
> >
> > +1 from me.
> >
> > -Edward
> >
> > On Jun 8, 2018, at 9:11 PM, evan at evan-borden.com <
> evan at evanrutledgeborden.dreamhosters.com> wrote:
> >
> > +1 We utilize a foldMap' in the freckle codebase.
> >
> > On Fri, Jun 8, 2018 at 1:10 PM, Daniel Cartwright <chessai1996 at gmail.com>
> wrote:
> >>
> >> +1
> >>
> >> On Fri, Jun 8, 2018 at 9:20 AM Andrew Martin <andrew.thaddeus at gmail.com>
> wrote:
> >>>
> >>> I propose adding another method to the Foldable typeclass: foldMap'
> >>>
> >>> This has the same behavior as foldMap except that it is strict in the
> accumulator. This can lead to considerable performance gains when the user
> knows that monoidal append is strict both arguments. Consider the following
> example (available as a gist at https://gist.github.com/andrewthad/
> f79b7022725532baf709514cf08c3955):
> >>>
> >>>   {-# LANGUAGE BangPatterns #-}
> >>>   {-# OPTIONS_GHC -O2 #-}
> >>>   import Gauge
> >>>   import Data.Foldable
> >>>   import qualified Data.Set as S
> >>>
> >>>   foldMap' :: (Monoid m, Foldable f) => (a -> m) -> f a -> m
> >>>   foldMap' f = foldl' (\ !acc a -> acc <> f a) mempty
> >>>
> >>>   numbers :: [Int]
> >>>   numbers = [1..4000]
> >>>
> >>>   intToSet :: Int -> S.Set Int
> >>>   intToSet i = S.singleton (mod i 10)
> >>>
> >>>   main :: IO ()
> >>>   main = defaultMain
> >>>     [ bench "lazy" $ whnf (foldMap intToSet) numbers
> >>>     , bench "strict" $ whnf (foldMap' intToSet) numbers
> >>>     ]
> >>>
> >>> Here are the results we get from running this:
> >>>
> >>>   benchmarked lazy
> >>>   time                 178.8 μs   (176.1 μs .. 183.1 μs)
> >>>                        0.996 R²   (0.993 R² .. 0.998 R²)
> >>>   mean                 180.8 μs   (179.1 μs .. 183.3 μs)
> >>>   std dev              7.242 μs   (5.856 μs .. 9.304 μs)
> >>>   variance introduced by outliers: 20% (moderately inflated)
> >>>
> >>>   benchmarked strict
> >>>   time                 108.4 μs   (106.1 μs .. 111.0 μs)
> >>>                        0.997 R²   (0.996 R² .. 0.999 R²)
> >>>   mean                 107.9 μs   (107.0 μs .. 109.3 μs)
> >>>   std dev              3.672 μs   (2.451 μs .. 6.220 μs)
> >>>   variance introduced by outliers: 15% (moderately inflated)
> >>>
> >>> These performance gains are considerable. It needs to be a method of
> Foldable and not just a function written using foldl' for the same reason
> that the lazy foldMap needs to be a method of Foldable. There are types for
> which the default implementation can be improved upon. This is a
> non-breaking change since there is a sensible default implementation.
> >>>
> >>> --
> >>> -Andrew Thaddeus Martin
> >>> _______________________________________________
> >>> Libraries mailing list
> >>> Libraries at haskell.org
> >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> >>
> >>
> >> _______________________________________________
> >> Libraries mailing list
> >> Libraries at haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> >>
> >
> >
> >
> > --
> > --
> > Evan Borden
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>



-- 
-Andrew Thaddeus Martin
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20180628/ad0a3ede/attachment.html>


More information about the Libraries mailing list