
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? Bob

On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie 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.
It's also quadratic in invocations of f, no? If your monad's (>>=) doesn't object to being left-associated (which is *not* the case for free monads), then I think iterateM n f i = foldl (>>=) (return i) $ replicate n f would be both correct and linear. If you're monad's (>>=) is itsef quadratic in time when left-associated, you can try applying a CPS transformation to fix the problem.[1] jcc [1] http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf

On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie 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.
It's also quadratic in invocations of f, no? If your monad's (>>=) doesn't object to being left-associated (which is *not* the case for free monads), then I think
iterateM n f i = foldl (>>=) (return i) $ replicate n f
But this isn't the same function – it only gives back the final result, not the intermediaries. Bob

I don't think scanl can work here, since the monadic action has to be
applied to the result of previous one and will have a side effect, so if you
build a list like
[return i, return i >>= f, return i >>= f >>= f, ...]
the first action will do nothing, the second action will have a single side
effect, but the third one will have 3 side effects instead of 2, because it
operates on the side-effect performed by the second one.
This seems to work (a combination of manual state monad and foldM, I could
also have used a state monad transformer I guess)
iterateM n f i = foldM collectEffect (i,[]) (replicate n f) >>= return .
reverse . snd
where
collectEffect (x,rs) f = f x >>= \y -> return (y,y:rs)
Ugly test:
var = unsafePerformIO $ newIORef 0
inc i = do
x <- readIORef var
let y = x+i
writeIORef var y
return y
results in
*Main> iterateM 10 inc 1
[1,2,4,8,16,32,64,128,256,512]
*Main> iterateM 10 inc 1
[513,1026,2052,4104,8208,16416,32832,65664,131328,262656]
but maybe this is not what you're looking for?
On Wed, Apr 8, 2009 at 5:30 PM, Thomas Davie
On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie 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.
It's also quadratic in invocations of f, no? If your monad's (>>=) doesn't object to being left-associated (which is *not* the case for free monads), then I think
iterateM n f i = foldl (>>=) (return i) $ replicate n f
But this isn't the same function – it only gives back the final result, not the intermediaries.
Bob_______________________________________________
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh, I could have written it in more point free style (with arguments
reversed) as
iterateM n i = fmap (reverse . snd) .
foldM collectEffect (i,[]) .
replicate n
where
collectEffect (x,rs) f = f x >>= \y -> return (y,y:rs)
and I'm sure collectEffect could also be improved, but I'm still in
newbieeee land
On Wed, Apr 8, 2009 at 6:33 PM, Peter Verswyvelen
I don't think scanl can work here, since the monadic action has to be applied to the result of previous one and will have a side effect, so if you build a list like [return i, return i >>= f, return i >>= f >>= f, ...]
the first action will do nothing, the second action will have a single side effect, but the third one will have 3 side effects instead of 2, because it operates on the side-effect performed by the second one.
This seems to work (a combination of manual state monad and foldM, I could also have used a state monad transformer I guess)
iterateM n f i = foldM collectEffect (i,[]) (replicate n f) >>= return . reverse . snd where collectEffect (x,rs) f = f x >>= \y -> return (y,y:rs)
Ugly test:
var = unsafePerformIO $ newIORef 0
inc i = do x <- readIORef var let y = x+i writeIORef var y return y
results in
*Main> iterateM 10 inc 1 [1,2,4,8,16,32,64,128,256,512] *Main> iterateM 10 inc 1 [513,1026,2052,4104,8208,16416,32832,65664,131328,262656]
but maybe this is not what you're looking for?
On Wed, Apr 8, 2009 at 5:30 PM, Thomas Davie
wrote: On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie 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.
It's also quadratic in invocations of f, no? If your monad's (>>=) doesn't object to being left-associated (which is *not* the case for free monads), then I think
iterateM n f i = foldl (>>=) (return i) $ replicate n f
But this isn't the same function – it only gives back the final result, not the intermediaries.
Bob_______________________________________________
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well okay, I don't really need the state since it is already in the list...
So cleaned up
iterateM n i =
fmap (tail . reverse) .
foldM collectEffect [i] .
replicate n
where
collectEffect xxs@(x:xs) f = fmap (:xxs) (f x)
But I'm sure it can be much simpler (I don't understand Claus' version :-)
On Wed, Apr 8, 2009 at 6:38 PM, Peter Verswyvelen
Oh, I could have written it in more point free style (with arguments reversed) as iterateM n i = fmap (reverse . snd) . foldM collectEffect (i,[]) . replicate n where collectEffect (x,rs) f = f x >>= \y -> return (y,y:rs)
and I'm sure collectEffect could also be improved, but I'm still in newbieeee land
On Wed, Apr 8, 2009 at 6:33 PM, Peter Verswyvelen
wrote: I don't think scanl can work here, since the monadic action has to be applied to the result of previous one and will have a side effect, so if you build a list like [return i, return i >>= f, return i >>= f >>= f, ...]
the first action will do nothing, the second action will have a single side effect, but the third one will have 3 side effects instead of 2, because it operates on the side-effect performed by the second one.
This seems to work (a combination of manual state monad and foldM, I could also have used a state monad transformer I guess)
iterateM n f i = foldM collectEffect (i,[]) (replicate n f) >>= return . reverse . snd where collectEffect (x,rs) f = f x >>= \y -> return (y,y:rs)
Ugly test:
var = unsafePerformIO $ newIORef 0
inc i = do x <- readIORef var let y = x+i writeIORef var y return y
results in
*Main> iterateM 10 inc 1 [1,2,4,8,16,32,64,128,256,512] *Main> iterateM 10 inc 1 [513,1026,2052,4104,8208,16416,32832,65664,131328,262656]
but maybe this is not what you're looking for?
On Wed, Apr 8, 2009 at 5:30 PM, Thomas Davie
wrote: On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie 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.
It's also quadratic in invocations of f, no? If your monad's (>>=) doesn't object to being left-associated (which is *not* the case for free monads), then I think
iterateM n f i = foldl (>>=) (return i) $ replicate n f
But this isn't the same function – it only gives back the final result, not the intermediaries.
Bob_______________________________________________
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, 2009-04-08 at 17:30 +0200, Thomas Davie wrote:
On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie 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.
It's also quadratic in invocations of f, no? If your monad's (>>=) doesn't object to being left-associated (which is *not* the case for free monads), then I think
iterateM n f i = foldl (>>=) (return i) $ replicate n f
But this isn't the same function – it only gives back the final result, not the intermediaries.
True. Should have read more carefully. jcc

|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 These function are not the same (sequence of scanl? try using print in f). Also, I seriously hope you are not looking for this line noise:-) iterateM' = (foldr op (const $ return []) .) . replicate where f `op` x = uncurry (<$>) . ((:) &&& ((x =<<) . f)) Because if you do, your penance for using it would involve demonstrating that this is equivalent (+-1), or not (and do not mention my name anywhere near it!-) Claus

On 8 Apr 2009, at 18:21, Claus Reinke wrote:
|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
These function are not the same (sequence of scanl? try using print in f). Also, I seriously hope you are not looking for this line noise:-)
No indeed – that's what I meant about the latter being quadratic – it runs the action far more times than the other.
iterateM' = (foldr op (const $ return []) .) . replicate where f `op` x = uncurry (<$>) . ((:) &&& ((x =<<) . f))
Because if you do, your penance for using it would involve demonstrating that this is equivalent (+-1), or not (and do not mention my name anywhere near it!-)
ghci tells me this: Prelude Control.Applicative Control.Arrow> let iterateM' = let f `op` x = uncurry (<$>) . ((:) &&& ((x=<<) . f)) in (foldr op (const $ return []) .) . replicate <interactive>:1:92: Ambiguous type variable `m' in the constraints: `Monad m' arising from a use of `return' at <interactive>: 1:92-100 `Functor m' arising from a use of `op' at <interactive>:1:80-81 Probable fix: add a type signature that fixes these type variable(s)

|No indeed – that's what I meant about the latter being quadratic – it |runs the action far more times than the other. 'quadratic time' usually refers to complexity, not different results, so I thought I'd mention it anyway. |ghci tells me this: |Prelude Control.Applicative Control.Arrow> let iterateM' = let f `op` |x = uncurry (<$>) . ((:) &&& ((x=<<) . f)) in (foldr op (const $ |return []) .) . replicate | |<interactive>:1:92: | Ambiguous type variable `m' in the constraints: | `Monad m' arising from a use of `return' at <interactive>: |1:92-100 | `Functor m' arising from a use of `op' at <interactive>:1:80-81 | Probable fix: add a type signature that fixes these type |variable(s) But surely you have not enabled the monomorphism restriction while avoiding explicit recursion?-) I should, of course, have removed those nasty points - sorry about that, hope noone got hurt - to leave us with: (foldr (flip (((uncurry (<$>).).).((((:)&&&).).((.).(=<<))))) (const $ return []).) . replicate there, much better, isn't it? So obvious and clear that it doesn't even need a name anymore - it is fully declarative and self-explanatory. And it typechecks, so it must be correct!-) And it passes a test, so it isn't wrong, either!-) *Main> ((foldr (flip (((uncurry (<$>).).).((((:)&&&).).((.).(=<<))))) (const $ return []).) . replicate) 3 print () () () () [(),(),()] Sorry, just couldn't resist:-) Now, how do I get that tongue out of my cheek?-) Claus

On Wed, Apr 8, 2009 at 4:57 PM, Thomas Davie
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

On 8 Apr 2009, at 19:05, Josef Svenningsson wrote:
On Wed, Apr 8, 2009 at 4:57 PM, Thomas Davie
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.
That one certainly seems very natural to me, now if only unfoldM existed :) Bob

On Wed, Apr 8, 2009 at 7:11 PM, Thomas Davie
On 8 Apr 2009, at 19:05, Josef Svenningsson wrote:
On Wed, Apr 8, 2009 at 4:57 PM, Thomas Davie
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.
That one certainly seems very natural to me, now if only unfoldM existed :)
Well, you can always write it yourself, but that might be a little
excessive if you only want it for iterateM. The other option is of course to make a library proposal. The thing is, most people never use unfolds so I don't know how likely it is to be included. Cheers, Josef
participants (5)
-
Claus Reinke
-
Jonathan Cast
-
Josef Svenningsson
-
Peter Verswyvelen
-
Thomas Davie