[Haskell-cafe] Minor issue with mapAccumR
Ross Paterson
ross at soi.city.ac.uk
Wed Feb 6 13:48:54 EST 2008
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
More information about the Libraries
mailing list