Graeme Moss writes

> A question born out only of curiosity:
> 
> Can anyone provide a definition of `thread' equivalent to this:
> 
> > thread :: Monad m => [a -> m a] -> a -> m a
> > thread []     a = return a
> > thread (k:ks) a = k a >>= thread ks
> 
> not using pattern matching (eg. using map or fold) that does not have
> a space leak?  You can swap the arguments round if necessary.  Here's
> an example of what it does:
> 
> thread [c1,c2] a
> = c1 a >>= thread [c2]
> = c1 a >>= (\b -> c2 b >>= thread [])
> = c1 a >>= (\b -> c2 b >>= (\c -> return c))
> 
> The following:
> 
> > thread :: Monad m => [a -> m a] -> a -> m a
> > thread ks a = foldl (>>=) (return a) ks
> 
> is equivalent but evaluates the entire list before starting to execute
> an application of (>>=):
> 
> foldl (>>=) (return a) [c1,c2]
> = foldl (>>=) (return a >>= c1) [c2]
> = foldl (>>=) ((return a >>= c1) >>= c2) []
> = (return a >>= c1) >>= c2
> 
> and the following:
> 
> > thread :: Monad m => [a -> m a] -> a -> m a
> > thread ks a = foldr (flip (>>=)) (return a) ks
> 
> reverses the order of the applications _and_ space leaks:
> 
> foldr (flip (>>=)) (return a) [c1,c2]
> = (flip (>>=)) c1 (foldr (flip (>>=)) (return a) [c2])
> = (foldr (flip (>>=)) (return a) [c2]) >>= c1
> = ((flip (>>=)) c2 (foldr (flip (>>=)) (return a) [])) >>= c1
> = ((foldr (flip (>>=)) (return a) []) >>= c2) >>= c1
> = (return a >>= c2) >>= c1
> 
> You can use any of the Prelude or Monad library functions.
> 
> Graeme.
> 
> PS. I don't know the answer, but no, this is not a homework
> exercise. :-)

Hmm. Seems not too difficult. But probably I am missing something.

> thread                :: (Monad m) => [a -> m a] -> a -> m a
> thread []     a       =  return a
> thread (k:ks) a       =  k a >>= thread ks

First Step. Rewrite the above definition so that the structural
recursion becomes apparent.

> thread []             =  \a -> return a
> thread (k:ks)         =  \a -> k a >>= thread ks

Second Step. Replace the explicit recursion.

> thread                =  foldr (\k sol -> \a -> k a >>= sol) return

Third Step. Tidying things up.

> thread                =  foldr (\k sol a -> k a >>= sol) return

I tested the definition using

> inc n                 =  print n >> return (n + 1)

and

do thread (replicate 100000 inc) 0; putStrLn "done"

Seems to work fine. Does this qualify as a solution?

Cheers, Ralf


Reply via email to