[GHC] #12173: foldl' semantics changed from 4.7 to 4.8

#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

#12173: foldl' semantics changed from 4.7 to 4.8 -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): See #7994 which introduced the change 072259c78f77d6fe7c36755ebe0123e813c34457 (also Phab:D393) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12173#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12173: foldl' semantics changed from 4.7 to 4.8 -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I should clarify that I'm not personally attached to either option. But the semantic change was not discussed, I suspect it was accidental, and it is inconsistent with `Foldable` defaults. I feel pretty strongly that there should only be ''one'' notion of `foldl'` in `base`, whichever that is. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12173#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12173: foldl' semantics changed from 4.7 to 4.8 -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I can confirm that this semantic change was accidental (I was picking this variant because it looks simpler). If the other one with `let` or `$!` fuses equally well, I’m all for changing it back and making it consistent. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12173#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12173: foldl' semantics changed from 4.7 to 4.8 -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duncan): I wholeheartedly endorse this accidental change! http://www.well-typed.com/blog/90/ (see especially the section at the end about which `foldl'`) The strictness of the original definition of `foldl'` was itself accidental. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12173#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12173: foldl' semantics changed from 4.7 to 4.8 -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:4 duncan]:
that blog-post is super confusing... carries an April 1st date, and yet it appears to meant seriously :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12173#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC