[Haskell-cafe] Dynamic choice of "reverse" implementation

Dan Doel dan.doel at gmail.com
Fri Sep 28 14:56:58 EDT 2007


On Friday 28 September 2007, David Benbennick wrote:
> On 9/28/07, Ross Paterson <ross at soi.city.ac.uk> wrote:
> > However one can define
> >
> >         reversor :: Traversable f => f a -> f a
> >
> > which returns something of the same shape, but with the contents
> > reversed.
>
> How?  Is it possible to define a version of foldl for Traversable?

At the very least, you can do this:

    {-# LANGUAGE FlexibleContexts #-}

    import Prelude             hiding (mapM)
    import Control.Monad       hiding (mapM)
    import Control.Monad.State hiding (mapM)

    import Data.Foldable    (toList)
    import Data.Traversable (mapM, Traversable(..))

    reversor :: Traversable t => t a -> t a
    reversor t = evalState (mapM (const pick) t) (reverse $ toList t)

    pick :: MonadState [a] m => m a
    pick = do (h:t) <- get ; put t ; return h

There may be something nicer out there, though.


More information about the Haskell-Cafe mailing list