[Haskell-cafe] Re: question - which monad to use?

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Mon Oct 2 12:38:23 EDT 2006


Tamas K Papp wrote:
> Hi,
> 
> I have a computation where a function is always applied to the
> previous result.  However, this function may not return a value (it
> involves finding a root numerically, and there may be no zero on the
> interval).  The whole problem has a parameter c0, and the function is
> also parametrized by the number of steps that have been taken
> previously.
> 
> To make things concrete,
> 
> type Failmessage = Int          -- this might be something more complex
> data Result a = Root a | Failure Failmessage -- guess I could use Either too
> 
> f :: Double -> Int -> Double 0 -> Result Double
> f c0 0 _ = c0
> f c0 j x = {- computation using x, parameters calculated from c0 and j -}
> 
> Then
> 
> c1 = f c0 0 c0
> c2 = f c0 1 c1
> c3 = f c0 2 c2
> ....
> 
> up to cn.
> 
> I would like to
> 
> 1) stop the computation when a Failure occurs, and store that failure
> 
> 2) keep track of intermediate results up to the point of failure, ie
> have a list [c1,c2,c3,...] at the end, which would go to cn in the
> ideal case of no failure.
> 
> I think that a monad would be the cleanest way to do this.  I think I
> could try writing one (it would be a good exercise, I haven't written
> a monad before).  I would like to know if there is a predefined one
> which would work.

There are a several ways to achieve your goal, most do not use monads.

*a) "The underappreciated unfold"*

    unfoldr :: (a -> Maybe (b,a)) -> a -> [b]

basically iterates a function

    g :: a -> Maybe (b,a)

and collects [b] until f fails with Nothing.

With your given function f, one can define

    g c0 (j,c) = case f c0 j c of
	Root c' -> Just (c',(j+1,c'))
	_       -> Nothing

and get the job done by

    results = unfoldr (g c0) (0,c0)

The only problem is that the failure message is lost. You can write your
own unfold, though:

   unfoldE ::
       (a -> Either Failmessage a) -> a -> ([a], Maybe Failmessage)



*b) tying the knot, building an infinite list*

    cs = Root c0 : [f c0 j ck | (j,Root ck) <- zip [0..] cs]

will yield

    cs [Root c0, Root c1, ..., Failure i] ++ _|_

Then, you just have to collect results:

    collect xs = (failure, [ck | Root ck <- ys])
        where
        isFailure (Failure i) = True
        isFailure _ = False
        (ys,failure:_) = break isFailure
    results = collect cs

Note that in this case, you always have to end your values with a
failure ("success as failure"). Alas, you didn't mention a stopping
condition, did you?



*c) the monadic way*
This is not the preferred solution and I'll only sketch it here. It only
makes sense if you have many different f whose calling order depends
heavily on their outcomes. Basically, your monad does: 2) keep track of
results (MonadWriter) and 2) may yield an error (MonadError). Note that
you want to keep track of results even if an error is yielded, so you
end up with

    type MyMonad a = ErrorT (Either Failmessage) (Writer [Double]) a

where ErrorT and Writer are from the Control.Monad.* modules.

    f :: Double -> Int -> Double -> MyMonad Double
    f c0 j ck = do
        {computation}
        if {screwed up}
            then fail "you too, Brutus"
            else tell {c_{k+1}}
        return {c_{k+1}}



*d) reconsider your definition of f, separate concerns *
The fact that the computation of ck depends on the iteration count j
makes me suspicious. If you are using j for convergence tests etc. only,
then it's not good.
The most elegant way is to separate concerns: first generate an infinite
list of approximations

    f :: Double -> Double -> Double
    f c0 ck = {c_{k+1}}

    cs = iterate (f c0)

and then look for convergence

    epsilon = 1e-12
    takeUntilConvergence []  = []
    takeUntilConvergence [x] = [x]
    takeUntilConvergence (x:x2:xs) =
        if abs (x - x2) <= epsilon
            then [x]
            else x:takeUntilConvergence (x2:xs)

or anything else (irregular behaviour, ...). If it's difficult to tell
from the cs whether things went wrong, but easy to tell from within f
(division by almost 0.0 etc.), you can always blend the separate
concerns approach into a) and b):

        -- iterate as infinite list
    iterate f x0 = let xs = x0 : map f xs in xs
        -- iterate as unfoldr
    iterate f x0 = unfoldr g x0
        where g x = let x' = f x in Just (x',x')


Regards,
apfelmus



More information about the Haskell-Cafe mailing list