proposal #2461: add Traversable generalizations of mapAccumL and mapAccumR

The proposal is to add the following functions to Data.Traversable, generalizing the list versions in Data.List: -- |The 'mapAccumL' function behaves like a combination of 'fmap' -- and 'foldl'; it applies a function to each element of a structure, -- passing an accumulating parameter from left to right, and returning -- a final value of this accumulator together with the new structure. mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- |The 'mapAccumR' function behaves like a combination of 'fmap' -- and 'foldr'; it applies a function to each element of a structure, -- passing an accumulating parameter from right to left, and returning -- a final value of this accumulator together with the new structure. mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) These functions are handy for things like labelling trees, zipping, etc. Deadline: 3 weeks

On Tue, Jul 22, 2008 at 12:12 PM, Ross Paterson
The proposal is to add the following functions to Data.Traversable, generalizing the list versions in Data.List:
-- |The 'mapAccumL' function behaves like a combination of 'fmap' -- and 'foldl'; it applies a function to each element of a structure, -- passing an accumulating parameter from left to right, and returning -- a final value of this accumulator together with the new structure. mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
-- |The 'mapAccumR' function behaves like a combination of 'fmap' -- and 'foldr'; it applies a function to each element of a structure, -- passing an accumulating parameter from right to left, and returning -- a final value of this accumulator together with the new structure. mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
These functions are handy for things like labelling trees, zipping, etc.
I take it these would be implemented using a state transformer monad?
That is, something along these lines:
mapAccumL f a tb = runState (mapM (\b -> State (\a -> f a b)) tb) a
Presumably, we don't want to include every possible specialization of
'traverse', but I can imagine it being awkward to simulate mapAccumL/R
with a state monad if the actual code is short.
Incidentally, is there a Backward applicative functor transfomer
defined anywhere?
newtype Backward f a = Backward { runBackward :: f a } deriving Functor
instance Applicative f => Applicative (Backward f) where
pure = Backward . pure
(Backward f) <*> (Backward a) = Backward (f <**> a)
It shows up in at least one of the early applicative functor papers,
and it seems like it would be handy for generalizing things like
mapAccumL vs mapAccumR.
--
Dave Menendez

On Tue, Jul 22, 2008 at 09:49:29PM -0400, David Menendez wrote:
On Tue, Jul 22, 2008 at 12:12 PM, Ross Paterson
wrote: mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
I take it these would be implemented using a state transformer monad?
Yes (actually the applicative functor and its mirror image). Full code in the patch attached to the ticket.
Presumably, we don't want to include every possible specialization of 'traverse', but I can imagine it being awkward to simulate mapAccumL/R with a state monad if the actual code is short.
Indeed, it's convenient for numbering elements of a container from the left or from the right: mapAccumL (\ n x -> (n+1, (n,x))) 0 mapAccumR (\ n x -> (n+1, (n,x))) 0 zipping with a sufficiently long list: mapAccumL (\ (x:xs) y -> (xs, (x,y))) xs0 and the list versions of these functions are already in Data.List (and the Haskell 98 List module).
Incidentally, is there a Backward applicative functor transfomer defined anywhere?
newtype Backward f a = Backward { runBackward :: f a } deriving Functor
instance Applicative f => Applicative (Backward f) where pure = Backward . pure (Backward f) <*> (Backward a) = Backward (f <**> a)
Probably in Conal or Edward Kmett's libraries. Data.Monoid has the Monoid version.

David Menendez
Incidentally, is there a Backward applicative functor transfomer defined anywhere?
newtype Backward f a = Backward { runBackward :: f a } deriving Functor
instance Applicative f => Applicative (Backward f) where pure = Backward . pure (Backward f) <*> (Backward a) = Backward (f <**> a)
My intuitive typechecker doesn't accept that. And GHCi 6.8.2 seems to agree (I had to enable GeneralizedNewtypeDeriving for obvious reasons). /tmp/foo.hs:7:0: Occurs check: cannot construct the infinite type: a = (a -> b) -> b When trying to generalise the type inferred for `<*>' Signature type: forall (f :: * -> *). (Applicative f) => forall a1 b1. Backward f (a1 -> b1) -> Backward f a1 -> Backward f b1 Type to generalise: forall a1 b1. Backward f (a1 -> b1) -> Backward f a1 -> Backward f b1 In the instance declaration for `Applicative (Backward f)' Did I misunderstand something? Regards, Michael Karcher

On Fri, Jul 25, 2008 at 10:12 AM, Michael Karcher
David Menendez
wrote: Incidentally, is there a Backward applicative functor transfomer defined anywhere?
newtype Backward f a = Backward { runBackward :: f a } deriving Functor
instance Applicative f => Applicative (Backward f) where pure = Backward . pure (Backward f) <*> (Backward a) = Backward (f <**> a)
My intuitive typechecker doesn't accept that. And GHCi 6.8.2 seems to agree (I had to enable GeneralizedNewtypeDeriving for obvious reasons). [..] Did I misunderstand something?
That's a typo on my part. I should have written "Backward (a <**> f)".
--
Dave Menendez

David Menendez
On Fri, Jul 25, 2008 at 10:12 AM, Michael Karcher
wrote: David Menendez
wrote: Incidentally, is there a Backward applicative functor transfomer defined anywhere?
newtype Backward f a = Backward { runBackward :: f a } deriving Functor
instance Applicative f => Applicative (Backward f) where pure = Backward . pure (Backward f) <*> (Backward a) = Backward (f <**> a)
My intuitive typechecker doesn't accept that. And GHCi 6.8.2 seems to agree (I had to enable GeneralizedNewtypeDeriving for obvious reasons). [..] Did I misunderstand something?
That's a typo on my part. I should have written "Backward (a <**> f)".
so you mean: Backward f <*> Backward a = Backward (a <**> f) ? According to the haddock of Control.Applicative, this line is semantically equivalent to Backward f <*> Backward a = Backward (f <*> a) So I don't see the point of this "transformer". It seems to do nothing, just as newtype Backward f a = Backward { runBackward :: f a } deriving (Functor, Applicative) would also do. Regards, Michael Karcher

Hi Michael On 28 Jul 2008, at 07:50, Michael Karcher wrote: David wrote (with patch applied):
newtype Backward f a = Backward { runBackward :: f a } deriving Functor
instance Applicative f => Applicative (Backward f) where pure = Backward . pure (Backward f) <*> (Backward a) = Backward (a <**> f)
You said:
According to the haddock of Control.Applicative, this line is semantically equivalent to Backward f <*> Backward a = Backward (f <*> a)
I'm not saying the haddock is entirely clear, but it certainly doesn't necessitate the interpretation you're making.
So I don't see the point of this "transformer". It seems to do nothing, just as newtype Backward f a = Backward { runBackward :: f a } deriving (Functor, Applicative) would also do.
Appearances can be deceptive, so why not actually try it? *Backward> traverse print ["bong", "bing"] "bong" "bing" [(),()] *Backward> runBackward $ traverse (Backward . print) ["bong", "bing"] "bing" "bong" [(),()] (<*>) does the function's effects before the argument's; (<**>) does the argument's effects before the function's. In contrast with monads, the applicative interface does not offer the ability to make the choice of one computation depend on the value of another (in Lindley/Wadler/Yallop terminology, applicative functors are "oblivious"). One consequence is that it's easy to reverse the order of computation. All the best Conor

Conor McBride
Michael wrote
David wrote (with patch applied): [...] (Backward f) <*> (Backward a) = Backward (a <**> f) According to the haddock of Control.Applicative, this line is semantically equivalent to Backward f <*> Backward a = Backward (f <*> a) I'm not saying the haddock is entirely clear, but it certainly doesn't necessitate the interpretation you're making.
OK, right. But the text "A variant of <*> with the arguments reversed" at least sounds like "<**> = flip <*>", which obviously is untrue then.
Appearances can be deceptive, so why not actually try it? I tried it, but too pure. I just checked whether some arguments are somehow reversed, but didn't pay care to the effects:
*Main> runBackward $ (pure (++)) <*> (pure "Hello") <*> (pure " World") "Hello World" *Main> runBackward $ (pure (^)) <*> (pure 1) <*> (pure 2) 1
*Backward> runBackward $ traverse (Backward . print) ["bong", "bing"] "bing" "bong" [(),()] Thanks for the convincing example.
In contrast with monads, the applicative interface does not offer the ability to make the choice of one computation depend on the value of another Yeah, right. That's the point of Applicative, if I remember the paper correctly.
All the best Thanks for the explanation.
Michael Karcher

Hi On 28 Jul 2008, at 09:48, Michael Karcher wrote:
Conor McBride
wrote: Michael wrote
David wrote (with patch applied): [...] (Backward f) <*> (Backward a) = Backward (a <**> f) According to the haddock of Control.Applicative, this line is semantically equivalent to Backward f <*> Backward a = Backward (f <*> a) I'm not saying the haddock is entirely clear, but it certainly doesn't necessitate the interpretation you're making.
OK, right. But the text "A variant of <*> with the arguments reversed" at least sounds like "<**> = flip <*>", which obviously is untrue then.
Yes, perhaps "A variant of <*> where the argument is computed before the function" might be more helpful. I can't help thinking that the definition might be the best documentation here.
Appearances can be deceptive, so why not actually try it? I tried it, but too pure. I just checked whether some arguments are somehow reversed, but didn't pay care to the effects:
*Main> runBackward $ (pure (++)) <*> (pure "Hello") <*> (pure " World") "Hello World" *Main> runBackward $ (pure (^)) <*> (pure 1) <*> (pure 2) 1
Indeed, the relevant laws guarantee that you need at least two effectful subcomputations to distinguish an applicative functor from its Backward companion. Hence
*Backward> runBackward $ traverse (Backward . print) ["bong", "bing"] "bing" "bong" [(),()]
In contrast with monads, the applicative interface does not offer the ability to make the choice of one computation depend on the value of another Yeah, right. That's the point of Applicative, if I remember the paper correctly.
Yes, it's a weaker demand, hence the resulting combinators are potentially more useful. Often, it's all you need. Cheers Conor

Excerpts from Michael Karcher's message of Mon Jul 28 10:48:34 +0200 2008:
Conor McBride
wrote: Michael wrote
David wrote (with patch applied): [...] (Backward f) <*> (Backward a) = Backward (a <**> f) According to the haddock of Control.Applicative, this line is semantically equivalent to Backward f <*> Backward a = Backward (f <*> a) I'm not saying the haddock is entirely clear, but it certainly doesn't necessitate the interpretation you're making.
OK, right. But the text "A variant of <*> with the arguments reversed" at least sounds like "<**> = flip <*>", which obviously is untrue then.
I've also understood "<**> = flip <*>" when reading the docs :( -- Nicolas Pouillard aka Ertai

Quoting Nicolas Pouillard
I've also understood "<**> = flip <*>" when reading the docs :(
Clearly the docs need improving. Does anyone have any comments on the proposal itself? ---------------------------------------------------------------- This message was sent using IMP, the Internet Messaging Program.

Excerpts from Ross Paterson's message of Fri Aug 01 16:16:04 +0200 2008:
Quoting Nicolas Pouillard
: I've also understood "<**> = flip <*>" when reading the docs :(
Clearly the docs need improving. Does anyone have any comments on the proposal itself?
I'm for the mapAccum{L,R} proposal, and the Backward, Applicative instance. -- Nicolas Pouillard aka Ertai

Ross Paterson wrote:
The proposal is to add the following functions to Data.Traversable,
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
It is useful as an education effort so that people can see how/which functions can be naturally generalized -- or if converting code from using Lists. (Probably it's useful in its own right, but I haven't used Traversable recently enough to be able to report on that.) I often thought that even Data.List.mapAccum[LR] is just on the edge of deserving to be its own function seperate from foldl/foldr anyway... -Isaac
participants (7)
-
Conor McBride
-
David Menendez
-
Isaac Dupree
-
Nicolas Pouillard
-
Ross Paterson
-
ross@soi.city.ac.uk
-
usenet@mkarcher.dialup.fu-berlin.de