Proposal: make minimumBy/maximumBy go through foldl', not foldr1

Lana Black lanablack at amok.cc
Wed Feb 10 22:09:15 UTC 2016


> Thanks for testing, but I’d be careful with small examples. It is not
> unlikely that GHC can “fully grasp” them and do wonders, possibly even
> fusing the lists, but with larger examples we’d get bad behavior.
> 
> And indeed, with "-O0", or with NOINLINE maximumBy, I very quickly fill
> my memory.
> 
> Too bad there is no foldl1' to easily verify that with that, we get the
> desired behavior even without -O.
> 
> Now this gets interesting. I’m wondering if there is a good way of
> implementing foldl1', so I looked at the default implementation of
> foldl1, which is:
> 
>     foldl1 :: (a -> a -> a) -> t a -> a
>     foldl1 f xs = fromMaybe (error "foldl1: empty structure")
>                     (foldl mf Nothing xs)
>       where
>         mf m y = Just (case m of
>                          Nothing -> y
>                          Just x  -> f x y)
> 
> This implements foldl1 via foldl and an accumulator _wrapped in a Maybe
> and case-analized in every step_. I sincerely hope that every instance
> overrides this by an more efficient version. And at least those
> Foldable instances with more than one element in Data.Foldable do...
> 
> Nevertheless, for the question of memory usage, a generic definition
> will do. And indeed, using
> 
>     foldl1' :: Foldable t => (a -> a -> a) -> t a -> a
>     foldl1' f xs = fromMaybe (error "foldl1': empty structure")
>                     (foldl' mf Nothing xs)
>       where
>         mf Nothing y = Just y
>         mf (Just x) y = x `seq` Just (f x y)
> 
> in your example, I get constant memory consumption as expected.
> 
> Greetings,
> Joachim
> 

I'm not sure whether foldl1' would be optimal for every Foldable
instance out there. Besides, as it was mentioned earier in this thread,
Haskell98 requires maximumBy to be lazy.
Anyway, switching to foldl1 is enough to fix the performance regression
(see https://ghc.haskell.org/trac/ghc/ticket/10830) introduced by FTP.


More information about the Libraries mailing list