[Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Peter Padawitz
A simplied version of Example 5-16 in Manna's classical book 
Mathematical Theory of Computation:


foo x = if x == 0 then 0 else foo (x-1)*foo (x+1)

If run with ghci, foo 5 does not terminate, i.e., Haskell does not look 
for all outermost redices in parallel. Why? For efficiency reasons?


It's a pity because a parallel-outermost strategy would be complete.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Bulat Ziganshin
Hello Peter,

Monday, February 9, 2009, 5:10:22 PM, you wrote:

 If run with ghci, foo 5 does not terminate, i.e., Haskell does not look
 for all outermost redices in parallel. Why? For efficiency reasons?

of course. if you will create new thread for every cpu instruction
executed, you will definitely never compute anything :D

you need to use `par`

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Robin Green
On Mon, 09 Feb 2009 15:10:22 +0100
Peter Padawitz peter.padaw...@udo.edu wrote:

 A simplied version of Example 5-16 in Manna's classical book 
 Mathematical Theory of Computation:
 
 foo x = if x == 0 then 0 else foo (x-1)*foo (x+1)
 
 If run with ghci, foo 5 does not terminate, i.e., Haskell does not
 look for all outermost redices in parallel. Why? For efficiency
 reasons?

I believe * is implemented in the normal way and thus is always strict
in both arguments.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Jochem Berndsen
Peter Padawitz wrote:
 A simplied version of Example 5-16 in Manna's classical book
 Mathematical Theory of Computation:

 foo x = if x == 0 then 0 else foo (x-1)*foo (x+1)

 If run with ghci, foo 5 does not terminate, i.e., Haskell does not look
 for all outermost redices in parallel. Why? For efficiency reasons?

 It's a pity because a parallel-outermost strategy would be complete.

(*) is strict in both arguments for Int. If you want to avoid this, you
could do
newtype X = X Int
and write your own implementation of (*) that is nonstrict.

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Iavor Diatchki
Hi,
Just for fun, here is the code that does this:

newtype Int' = I Int deriving Eq

instance Show Int' where
  show (I x) = show x

instance Num Int' where
  I x + I y = I (x + y)

  I 0 * _   = I 0
  I x * I y = I (x * y)

  I x - I y = I (x - y)

  abs (I x) = I (abs x)

  signum (I x)  = I (signum x)

  negate (I x)  = I (negate x)

  fromInteger n = I (fromInteger n)

foo x = if x == 0 then 0 else foo (x - 1) * foo (x + 1)

*Main foo 5 :: Int'
0

-Iavor


On Mon, Feb 9, 2009 at 7:19 AM, Jochem Berndsen joc...@functor.nl wrote:
 Peter Padawitz wrote:
 A simplied version of Example 5-16 in Manna's classical book
 Mathematical Theory of Computation:

 foo x = if x == 0 then 0 else foo (x-1)*foo (x+1)

 If run with ghci, foo 5 does not terminate, i.e., Haskell does not look
 for all outermost redices in parallel. Why? For efficiency reasons?

 It's a pity because a parallel-outermost strategy would be complete.

 (*) is strict in both arguments for Int. If you want to avoid this, you
 could do
 newtype X = X Int
 and write your own implementation of (*) that is nonstrict.

 --
 Jochem Berndsen | joc...@functor.nl
 GPG: 0xE6FABFAB
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Max Rabkin
On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki
iavor.diatc...@gmail.com wrote:
  I 0 * _   = I 0
  I x * I y = I (x * y)

Note that (*) is now non-commutative (w.r.t. _|_). Of course, that's
what we need here, but it means that the obviously correct
transformation of

 foo x = if x == 0 then 0 else foo (x - 1) * foo (x + 1)

into

foo' x = if x == 0 then 0 else foo' (x + 1) * foo' (x - 1)

is *not* in fact correct.

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


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Thomas Davie


On 10 Feb 2009, at 07:57, Max Rabkin wrote:


On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki
iavor.diatc...@gmail.com wrote:

I 0 * _   = I 0
I x * I y = I (x * y)


Note that (*) is now non-commutative (w.r.t. _|_). Of course, that's
what we need here, but it means that the obviously correct
transformation of


just to improve slightly:

I 0 |* _   = I 0
I x |* I y = I (x * y)

_ *| I 0   = I 0
I x *| I y = I (x * y)

I x * | y = (I x |* I y) `unamb` (I x *| I y)

Now it is commutative :)

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


Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread George Pollard
On Tue, 2009-02-10 at 08:03 +0100, Thomas Davie wrote:
 On 10 Feb 2009, at 07:57, Max Rabkin wrote:
 
  On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki
  iavor.diatc...@gmail.com wrote:
  I 0 * _   = I 0
  I x * I y = I (x * y)
 
  Note that (*) is now non-commutative (w.r.t. _|_). Of course, that's
  what we need here, but it means that the obviously correct
  transformation of
 
 just to improve slightly:
 
 I 0 |* _   = I 0
 I x |* I y = I (x * y)
 
 _ *| I 0   = I 0
 I x *| I y = I (x * y)
 
 I x * | y = (I x |* I y) `unamb` (I x *| I y)
 
 Now it is commutative :)
 
 Bob

See `parCommute` from the 'lub' package :)


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe