Proposal: Add mapAccumLM and mapAccumRM to Data.Traversable

David Feuer david.feuer at gmail.com
Mon Sep 3 04:22:02 UTC 2018


If I understand you correctly, the main idea here is

maLM, maRM
  :: (Traversable t, Monad m)
  => (b -> StateT a m c)
  -> t b
  -> StateT a m (t c)
maLM = traverse
maRM f t = getReverse <$> traverse f (Reverse t)

where Reverse is from Data.Functor.Reverse. The main annoyance trying to
implement the precise functions you've requested from those is really
impedance matching between the different argument and result orders. As I
see it, there are two problems:

1. The standard StateT uses result pairs that are swapped from the way they
should conventionally be. I would speculate that this may derive from a
history of thinking about state transformers in the context of parsing,
where "the rest of the input" seems like it should sit to the right of the
present result. Your StateLT strikes me as the "right" StateT, and I would
support its addition to the ecosystem somewhere.

2. The functions you request take their arguments in the "wrong" order. I
think it's more natural to go with this type:

mapAccumLM, mapAccumRM
  :: (Traversable t, Monad m)
  => (b -> a -> m (a,c)) -> t b -> a -> m (a, t c)

On Sun, Sep 2, 2018, 11:38 PM Reed Mullanix <reedmullanix at gmail.com> wrote:

> I propose adding a pair of functions to Data.Traversable: mapAccumLM and
> mapAccumRM with the type '(Traversable t, Monad m) => (a -> b -> m (a,c))
> -> a -> t b -> m (a, t c)'. These would behave exactly the same as
> mapAccumL and mapAccumR, but would allow the addition of monadic effects.
>
> This would allow the traversal of structures with an accumulator, without
> resorting to using foldlM or foldrM, both of which require the extra
> boilerplate of reconstructing the structure after applying the action,
> which can be somewhat frustrating and error-prone.
>
> A possible implementation would be to add transformer counterparts to
> StateL/StateR in Data.Functor.Util: (gist:
> https://gist.github.com/TOTBWF/dc6020be28df7b00372ab8e507aa54b7)
>
>     newtype StateLT s m a = StateLT { runStateLT :: s -> m (s,a) }
>
>     instance (Functor m) => Functor (StateLT s m) where
>       fmap f (StateLT k) = StateLT $ \s -> fmap (\(s',a) -> (s', f a)) $ k
> s
>
>     instance Monad m => Applicative (StateLT s m) where
>       pure a = StateLT $ \s -> return (s, a)
>       StateLT kf <*> StateLT kv = StateLT $ \s -> do
>         (s', f) <- kf s
>         (s'', v) <- kv s'
>         return (s'', f v)
>       liftA2 f (StateLT kx) (StateLT ky) = StateLT $ \s -> do
>         (s', x) <- kx s
>         (s'', y) <- ky s'
>         return (s'', f x y)
>
>     mapAccumLM :: (Monad m, Traversable t) => (a -> b -> m (a,c)) -> a ->
> t b -> m (a, t c)
>     mapAccumLM f s t = runStateLT (traverse (StateLT . flip f) t) s
>
>     newtype StateRT s m a = StateRT { runStateRT :: s -> m (s,a) }
>
>     type StateR s = StateRT s Identity
>
>     instance (Functor m) => Functor (StateRT s m) where
>       fmap f (StateRT k) = StateRT $ \s -> fmap (\(s',a) -> (s', f a)) $ k
> s
>
>     instance Monad m => Applicative (StateRT s m) where
>       pure a = StateRT $ \s -> return (s, a)
>       StateRT kf <*> StateRT kv = StateRT $ \s -> do
>         (s', v) <- kv s
>         (s'', f) <- kf s'
>         return (s'', f v)
>       liftA2 f (StateRT kx) (StateRT ky) = StateRT $ \s -> do
>         (s', y) <- ky s
>         (s'', x) <- kx s'
>         return (s'', f x y)
>
>     mapAccumRM :: (Monad m, Traversable t) => (a -> b -> m (a,c)) -> a ->
> t b -> m (a, t c)
>     mapAccumRM f s t = runStateRT (traverse (StateRT . flip f) t) s
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20180903/e879cf20/attachment.html>


More information about the Libraries mailing list