<div dir="auto"><div>If I understand you correctly, the main idea here is</div><div dir="auto"><br></div><div dir="auto">maLM, maRM</div><div dir="auto">  :: (Traversable t, Monad m)</div><div dir="auto">  => (b -> StateT a m c)</div><div dir="auto">  -> t b</div><div dir="auto">  -> StateT a m (t c)</div><div dir="auto">maLM = traverse</div><div dir="auto">maRM f t = getReverse <$> traverse f (Reverse t)</div><div dir="auto"><br></div><div dir="auto">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:</div><div dir="auto"><br></div><div dir="auto">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.</div><div dir="auto"><br></div><div dir="auto">2. The functions you request take their arguments in the "wrong" order. I think it's more natural to go with this type:</div><div dir="auto"><br></div><div dir="auto"><span style="font-family:sans-serif">mapAccumLM, mapAccumRM</span></div><div dir="auto"><span style="font-family:sans-serif">  :: (Traversable t, Monad m)</span></div><div dir="auto"><span style="font-family:sans-serif">  => (b -> a -> m (a,c)) -> t b -> a -> m (a, t c)</span></div><div dir="auto"><br><div class="gmail_quote" dir="auto"><div dir="ltr">On Sun, Sep 2, 2018, 11:38 PM Reed Mullanix <<a href="mailto:reedmullanix@gmail.com" target="_blank" rel="noreferrer">reedmullanix@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div dir="ltr">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.<br><br>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.<br><br>A possible implementation would be to add transformer counterparts to StateL/StateR in Data.Functor.Util: (gist: <a href="https://gist.github.com/TOTBWF/dc6020be28df7b00372ab8e507aa54b7" rel="noreferrer noreferrer" target="_blank">https://gist.github.com/TOTBWF/dc6020be28df7b00372ab8e507aa54b7</a>)<br><br>    newtype StateLT s m a = StateLT { runStateLT :: s -> m (s,a) }<br><br>    instance (Functor m) => Functor (StateLT s m) where<br>      fmap f (StateLT k) = StateLT $ \s -> fmap (\(s',a) -> (s', f a)) $ k s<br><br>    instance Monad m => Applicative (StateLT s m) where<br>      pure a = StateLT $ \s -> return (s, a)<br>      StateLT kf <*> StateLT kv = StateLT $ \s -> do<br>        (s', f) <- kf s<br>        (s'', v) <- kv s'<br>        return (s'', f v)<br>      liftA2 f (StateLT kx) (StateLT ky) = StateLT $ \s -> do<br>        (s', x) <- kx s<br>        (s'', y) <- ky s'<br>        return (s'', f x y)<br><br>    mapAccumLM :: (Monad m, Traversable t) => (a -> b -> m (a,c)) -> a -> t b -> m (a, t c)<br>    mapAccumLM f s t = runStateLT (traverse (StateLT . flip f) t) s<br><br>    newtype StateRT s m a = StateRT { runStateRT :: s -> m (s,a) }<br><br>    type StateR s = StateRT s Identity<br><br>    instance (Functor m) => Functor (StateRT s m) where<br>      fmap f (StateRT k) = StateRT $ \s -> fmap (\(s',a) -> (s', f a)) $ k s<br><br>    instance Monad m => Applicative (StateRT s m) where<br>      pure a = StateRT $ \s -> return (s, a)<br>      StateRT kf <*> StateRT kv = StateRT $ \s -> do<br>        (s', v) <- kv s<br>        (s'', f) <- kf s'<br>        return (s'', f v)<br>      liftA2 f (StateRT kx) (StateRT ky) = StateRT $ \s -> do<br>        (s', y) <- ky s<br>        (s'', x) <- kx s'<br>        return (s'', f x y)<br><br>    mapAccumRM :: (Monad m, Traversable t) => (a -> b -> m (a,c)) -> a -> t b -> m (a, t c)<br>    mapAccumRM f s t = runStateRT (traverse (StateRT . flip f) t) s<br><br></div></div>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" rel="noreferrer noreferrer" target="_blank">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote></div></div></div>