[EMAIL PROTECTED] wrote:
G'day Tamas.

Quoting Tamas K Papp <[EMAIL PROTECTED]>:

f is an a->a function, and there is a stopping rule
goOn(a,anext) :: a a -> Bool which determines when to stop.  The
algorithm looks like this (in imperative pseudocode):

a = ainit

while (true) {
      anext <- f(a)
      if (goOn(a,anext))
         a <- anext
      else
         stop and return anext
}

Here are a couple more suggestions.

First, this function scans an infinite list and stops when p x1 x2
is true for two adjacent elements x1 and x2:

    findFixpoint p (x1:xs@(x2:_))
        | p x1 x2   = x2
        | otherwise = findFixpoint p xs

Then you just need to pass it [ainit, f ainit, f (f ainit), ...]:

    findFixpoint dontGoOn (iterate f ainit)

Note that the function to pass to findFixpoint here is the condition
to use to _stop_.

The compiler may not deforest that list, so creating the list may be a small overhead of this method.


If you're comfortable with monads, it's possible to directly simulate
complex imperative control flow.  It's not recommended to do this
unless the flow is very complex, but here we are for the record:

    import Control.Monad.Cont

    -- I used a Newton-Raphson square root evaluation for testing,
    -- but it has the same structure as your algorithm.
    mysqrt :: Double -> Double
    mysqrt x
      = runCont (callCC loop) id
      where
        ainit = x * 0.5

        f x = 0.5 * (a + x/a)

        goOn a1 a2 = abs (a1 - a2) > 1e-5

        loop break
          = loop' ainit
          where
            loop' a
              = do
                let anext = f a
                if goOn a anext
                 then loop' anext
                 else break anext

callCC defines a point outside the loop that you can "break" to.
You simply call that function (called a "continuation") and the
loop is broken.

Cheers,
Andrew Bromage

Note that "f x" should be "f a" above. But I like it. My version of the above looks like

import Control.Monad.Cont

mysqrt :: Double -> Double
mysqrt x = doWhile goOn f aInit
  where
    aInit = x * 0.5
    f a = 0.5 * (a + x/a)
    goOn a1 a2 = abs (a1 - a2) > 1e-5

doWhile :: (a -> a -> Bool) -> (a -> a) -> a -> a
doWhile goOn f x0 = runCont (callCC withBreak) id
where withBreak break = let loop x = do let x' = f x
                          when (not (goOn x x')) (break x')
                          loop x'
          in loop x0


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to