
I'm not sure whether this would be considered worth fixing right away, or if we should wait until some other major compatibility breaking language change to fix it, but it appears that somehow the parameters to the function passed to mapAccumR are flipped relative to their natural order. To show what I mean, here is some code: Prelude Data.List> mapAccumR (\x y -> (concat ["(f ",x," ",y,")"], concat ["(g ",x," ",y,")"])) "z" ["1","2","3"] ("(f (f (f z 3) 2) 1)",["(g (f (f z 3) 2) 1)","(g (f z 3) 2)","(g z 3)"]) You can see here that the list is flipped over in the process, even though the right fold structure is there, it ends up looking like a left fold over the reverse of the list. One would want the law: fst . mapAccumR f z = foldr (fst . f) z to be true, but instead we have: fst . mapAccumR (flip f) z = foldr (fst . f) z You can see that structurally if we flip the parameters in the above example: Prelude Data.List> mapAccumR (\y x -> (concat ["(f ",x," ",y,")"], concat ["(g ",x," ",y,")"])) "z" ["1","2","3"] ("(f 1 (f 2 (f 3 z)))",["(g 1 (f 2 (f 3 z)))","(g 2 (f 3 z))","(g 3 z)"]) I also have some diagrams on http://cale.yi.org/index.php/Fold_Diagrams (near the end) displaying the difference, and that's where I first noticed it. Are many people using mapAccumR? How much would it hurt to change it? - Cale

On Tue, 5 Feb 2008, Cale Gibbard wrote:
Are many people using mapAccumR? How much would it hurt to change it?
I cannot remember having ever used mapAccumR, but I used mapAccumL where I used mapM on State monad before, in order to avoid dependency on MTL (and thus non-Haskell-98 features).

On Tue, Feb 05, 2008 at 12:03:38AM -0500, Cale Gibbard wrote:
Are many people using mapAccumR? How much would it hurt to change it?
It's specified in the Haskell 98 Report, so changing it is a big deal. Personally, I think the types should have been mapAccumL :: (s -> a -> (b,s)) -> s -> [a] -> ([b],s) mapAccumR :: (a -> s -> (s,b)) -> [a] -> s -> (s,[b]) to show which direction the state flows. I can't resist observing that these functions generalize to Traversable, so they can be used for numbering elements, zipping with a Stream, etc: -- left-to-right state transformer newtype StateL s a = StateL { runStateL :: s -> (s, a) } instance Functor (StateL s) where fmap f (StateL k) = StateL ((id *** f) . k) instance Applicative (StateL s) where pure x = StateL (\ s -> (s, x)) StateL kf <*> StateL kv = StateL $ \ s -> let (s', f) = kf s (s'', v) = kv s' in (s'', f v) mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s -- right-to-left state transformer newtype StateR s a = StateR { runStateR :: s -> (s, a) } instance Functor (StateR s) where fmap f (StateR k) = StateR ((id *** f) . k) instance Applicative (StateR s) where pure x = StateR (\ s -> (s, x)) StateR kf <*> StateR kv = StateR $ \ s -> let (s', v) = kv s (s'', f) = kf s' in (s'', f v) mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) mapAccumR f s t = runStateR (traverse (StateR . flip f) t) s

On 06/02/2008, Ross Paterson
On Tue, Feb 05, 2008 at 12:03:38AM -0500, Cale Gibbard wrote:
Are many people using mapAccumR? How much would it hurt to change it?
It's specified in the Haskell 98 Report, so changing it is a big deal. Personally, I think the types should have been
mapAccumL :: (s -> a -> (b,s)) -> s -> [a] -> ([b],s) mapAccumR :: (a -> s -> (s,b)) -> [a] -> s -> (s,[b])
to show which direction the state flows.
participants (3)
-
Cale Gibbard
-
Henning Thielemann
-
Ross Paterson