Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-17 Thread Tamas K Papp
On Thu, Aug 17, 2006 at 01:23:19AM -0400, [EMAIL PROTECTED] wrote:
> G'day all.
> 
> Quoting Chris Kuklewicz <[EMAIL PROTECTED]>:
> 
> > The compiler may not deforest that list, so creating the list may be a small
> > overhead of this method.
> 
> And in return, you get:
> 
> - Code that is smaller than the imperative version, AND
> - a reusable function, making the next incarnation of
>   an algorithm like this even shorter.
> 
> For most interesting cases, the cost of f and goOn will surely dominate
> anyway.
> 
> > Note that "f x" should be "f a" above.
> 
> Yes, you're right.  I abstracted out "f" after testing and before
> posting.

Chris, Christian, Andrew, Antti-Juhani and Ivan,

Thanks for your answers, they were very enlightening (though it will
take some time to understand everything).  Haskell looks even more
elegant than Scheme...

Best,

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


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread ajb
G'day all.

Quoting Chris Kuklewicz <[EMAIL PROTECTED]>:

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

And in return, you get:

- Code that is smaller than the imperative version, AND
- a reusable function, making the next incarnation of
  an algorithm like this even shorter.

For most interesting cases, the cost of f and goOn will surely dominate
anyway.

> Note that "f x" should be "f a" above.

Yes, you're right.  I abstracted out "f" after testing and before
posting.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread Chris Kuklewicz

[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


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread ajb
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_.

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread ivan gomez rodriguez

Chris Kuklewicz wrote:

Tamas K Papp wrote:

Hi,

I am a newbie learning Haskell.  I have used languages with functional
features before (R, Scheme) but not purely functional ones without
side-effects.

Most of the programming I do is numerical (I am an economist).  I
would like to know how to implement the iterative algorithm below in
Haskell.

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
}

For example, f can be a contraction mapping and goOn a test based on
the metric.  I don't know how to do this in a purely functional
language, especially if the object a is large and I would like it to
be garbage collected if the iteration goes on.

Thank you,

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


iterUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a
iterUntil goOn f aInit =
  let loop a =
let a' = f a
in if goOn a a'
 then loop a'-- tail recursive (so "a" will be collected)
 else a'
  in loop aInit


In Haskell you can do this

iterUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a
iterUntil goOn f a  | goOn a anext = iterUntil goOn f anext
  | otherwise= anext
  where anext = f a


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


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread Antti-Juhani Kaijanaho
Tamas K Papp wrote:
> 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
> }
> 
> For example, f can be a contraction mapping and goOn a test based on
> the metric.  I don't know how to do this in a purely functional
> language, especially if the object a is large and I would like it to
> be garbage collected if the iteration goes on.

The idea is to make the iteration variables arguments to a
tail-recursive function:

let foo a | goOn a anext = foo anext
  | otherwise= anext
where anext = f a
in foo ainit


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


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread Chris Kuklewicz

Tamas K Papp wrote:

Hi,

I am a newbie learning Haskell.  I have used languages with functional
features before (R, Scheme) but not purely functional ones without
side-effects.

Most of the programming I do is numerical (I am an economist).  I
would like to know how to implement the iterative algorithm below in
Haskell.

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
}

For example, f can be a contraction mapping and goOn a test based on
the metric.  I don't know how to do this in a purely functional
language, especially if the object a is large and I would like it to
be garbage collected if the iteration goes on.

Thank you,

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


iterUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a
iterUntil goOn f aInit =
  let loop a =
let a' = f a
in if goOn a a'
 then loop a'-- tail recursive (so "a" will be collected)
 else a'
  in loop aInit

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


[Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread Tamas K Papp
Hi,

I am a newbie learning Haskell.  I have used languages with functional
features before (R, Scheme) but not purely functional ones without
side-effects.

Most of the programming I do is numerical (I am an economist).  I
would like to know how to implement the iterative algorithm below in
Haskell.

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
}

For example, f can be a contraction mapping and goOn a test based on
the metric.  I don't know how to do this in a purely functional
language, especially if the object a is large and I would like it to
be garbage collected if the iteration goes on.

Thank you,

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