[Haskell-cafe] A challenge

Josef Svenningsson josef.svenningsson at gmail.com
Wed Apr 8 13:05:14 EDT 2009


On Wed, Apr 8, 2009 at 4:57 PM, Thomas Davie <tom.davie at gmail.com> wrote:
>
> We have two possible definitions of an "iterateM" function:
>
> iterateM 0 _ _ = return []
> iterateM n f i = (i:) <$> (iterateM (n-1) f =<< f i)
>
> iterateM n f i = sequence . scanl (>>=) (return i) $ replicate n f
>
> The former uses primitive recursion, and I get the feeling it should be
better written without it.  The latter is quadratic time – it builds up a
list of monadic actions, and then runs them each in turn.
>
> Can anyone think of a version that combines the benefits of the two?

There seems to be a combinator missing in Control.Monad. Several people have
suggested that iterateM should be implemented using a fold. But that seems
very unnatural, we're trying to *build* a list, not *consume* it. This
suggests that we should use an unfold function instead. Now, I haven't found
one in the standard libraries that works for monads but arguably there
should be one. So, let's pretend that the following function exists:
unfoldM :: Monad m => (b -> m (Maybe(a,b))) -> b -> m [a]

Then the implementation of iterateM becomes more natural:
\begin{code}
iterateM n f i = unfoldM g (n,i)
 where g (0,i) = return Nothing
       g (n,i) = do j <- f i
                    return (Just (i,(n-1,j)))
\end{code}
I'm not sure whether this version is to your satisfaction but it's quite
intuitive IMHO.

Here's the function I used to test various versions of iterateM:
\begin{code}
test it = it 4 (\i -> putStrLn (show i) >> return (i+1)) 0
\end{code}

Cheers,

Josef
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090408/d0efb3b2/attachment.htm


More information about the Haskell-Cafe mailing list