[GHC] #12173: foldl' semantics changed from 4.7 to 4.8
GHC
ghc-devs at haskell.org
Thu Jun 9 16:59:33 UTC 2016
#12173: foldl' semantics changed from 4.7 to 4.8
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Core | Version: 7.10.2
Libraries |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Runtime crash
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
`foldl'` is now defined as
{{{#!hs
foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b
{-# INLINE foldl' #-}
foldl' k z0 xs =
foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> z `seq` fn (k z v)))
(id :: b -> b) xs z0
}}}
As far as I can tell, the Haskell 2010 report does not specify anything
about the behavior of `foldl'`. In base 4.7, it was defined
{{{#!hs
foldl' :: (b -> a -> b) -> b -> [a] -> b
foldl' f z0 xs0 = lgo z0 xs0
where lgo z [] = z
lgo z (x:xs) = let z' = f z x in z' `seq` lgo z' xs
}}}
These are ''not'' equivalent. In particular, with the old `foldl'`,
{{{#!hs
foldl' (\_ _ -> 3) undefined "hello"
}}}
evaluates to `3`, but with the new one, it throws an exception. If the old
semantics are preferred, we can get them with
{{{#!hs
foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b
{-# INLINE foldl' #-}
foldl' k z0 xs =
foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> fn $! k z v)) (id :: b
-> b) xs z0
}}}
The ''old'' semantics match the default `Foldable` instance. The advantage
of the ''new'' semantics is that they're more consistent about strictness
(unconditionally strict in the accumulator), but that blocks out idioms
like
{{{#!hs
foldl' f (error "Empty list") ...
}}}
I don't remember this being discussed.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12173>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list