On Mon, Nov 3, 2014 at 6:51 PM, David Feuer <david.feuer@gmail.com> wrote:As Duncan Coutts explains toward the end of http://www.well-typed.com/blog/90/ (which proposes something else I personally *don't* endorse), foldl', the strict foldl, isn't actually strict enough. In particular, it's only conditionally strict in the initial value for the accumulator:foldl' (\_ x -> x) undefined [3] = 3Why does this matter? Strictness analysis needs to look at (and be able to look at) the function passed to foldl' to determine whether the expression is strict in the initial value. foldl'-as-foldr tends to complicate this sort of analysis already.Proposal: make foldl' unconditionally strict in the initial accumulator value, both in GHC.List and in (the default definition in) Data.Foldable, and make foldr' in Data.Foldable unconditionally strict in the initial value of its accumulator.Specifically,
foldl' k z0 xs =
foldr (\v fn z -> z `seq` fn (k z v)) id xs z0would change to
foldl' k !z0 xs =
foldr (\v fn z -> z `seq` fn (k z v)) id xs z0There are valid[1] uses of `foldl'` that would be broken by this change, e.g.:
{-# LANGUAGE BangPatterns #-}
import Data.List (foldl')
foldl2' k !z0 xs =
foldr (\v fn z -> z `seq` fn (k z v)) id xs z0
last1 = foldl' (flip const) (error "last1")
last2 = foldl2' (flip const) (error "last2")
main :: IO ()
main = do
let list = [1, 2, 3] :: [Int]
print $ last1 list
print $ last2 listThe current foldl' allows us to implement a `last` function, the new one does not. You can argue that there are far better ways to write `last` (and Duncan points that out in his blog post). But I'd like to have a better understanding of how much (silent) breakage this change would introduce before we move ahead with it, as well as how much of a benefit it might provide.
Michael[1] For some definition of valid.