Proposal: Make default impls for foldl1 and foldr1 lazier

We currently have (in Data.Foldable) foldr1 :: (a -> a -> a) -> t a -> a foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x Nothing = Just x mf x (Just y) = Just (f x y) and something similar for foldl1. This is strict in the entire spine, unlike the list version, because it has to get all the way to the end of the list before it starts laying down Justs. I propose we change this to the obvious: foldr1 :: (a -> a -> a) -> t a -> a foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x r = Just $ case r of Nothing -> x Just y -> f x y Since GHC 7.10.1 is fast approaching, I doubt we have the usual two weeks to discuss this, so please speak up as soon as you can if you have concerns.

+1. Or, for the friends of point-free programming, foldr f = fromMaybe (error "foldr1: empty structure") . foldr (\ x -> Just . maybe x (f x)) Nothing On 29.10.2014 20:08, David Feuer wrote:
We currently have (in Data.Foldable)
foldr1 :: (a -> a -> a) -> t a -> a foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x Nothing = Just x mf x (Just y) = Just (f x y)
and something similar for foldl1. This is strict in the entire spine, unlike the list version, because it has to get all the way to the end of the list before it starts laying down Justs. I propose we change this to the obvious:
foldr1 :: (a -> a -> a) -> t a -> a foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x r = Just $ case r of Nothing -> x Just y -> f x y
Since GHC 7.10.1 is fast approaching, I doubt we have the usual two weeks to discuss this, so please speak up as soon as you can if you have concerns.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel@gu.se http://www2.tcs.ifi.lmu.de/~abel/

+1 from me.
On Wed, Oct 29, 2014 at 3:08 PM, David Feuer
We currently have (in Data.Foldable)
foldr1 :: (a -> a -> a) -> t a -> a foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x Nothing = Just x mf x (Just y) = Just (f x y)
and something similar for foldl1. This is strict in the entire spine, unlike the list version, because it has to get all the way to the end of the list before it starts laying down Justs. I propose we change this to the obvious:
foldr1 :: (a -> a -> a) -> t a -> a foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x r = Just $ case r of Nothing -> x Just y -> f x y
Since GHC 7.10.1 is fast approaching, I doubt we have the usual two weeks to discuss this, so please speak up as soon as you can if you have concerns.
-- You received this message because you are subscribed to the Google Groups "haskell-core-libraries" group. To unsubscribe from this group and stop receiving emails from it, send an email to haskell-core-libraries+unsubscribe@googlegroups.com. For more options, visit https://groups.google.com/d/optout.

+1
lambdacase, anyone? :P
where
mf x = Just . \case
Nothing -> x
Just y -> f x y
-- Dan Burton
On Sat, Nov 1, 2014 at 6:30 PM, John Wiegley
Edward Kmett
writes: +1 from me.
+1 from me too.
John _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (5)
-
Andreas Abel
-
Dan Burton
-
David Feuer
-
Edward Kmett
-
John Wiegley