[Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
I was under the impression that operations performed in monads (in this
case, the IO monad) were lazy. (Certainly, every time I make the
opposite assumption, my code fails :P .) Which doesn't explain why the
following code fails to terminate:

  iRecurse :: (Num a) = IO a
  iRecurse = do
recurse - iRecurse
return 1

  main = (putStrLn . show) = iRecurse

Any pointers to a good explanation of when the IO monad is lazy?


=== The long story ===

I wrote a function unfold with type signature (([a] - a) - [a]), for
generating a list in which each element can be calculated from all of
the previous elements.

  unfold :: ([a] - a) - [a]
  unfold f = unfold1 f []

  unfold1 :: ([a] - a) - [a] - [a]
  unfold1 f l = f l : unfold1 f (f l : l)

Now I'm attempting to do the same thing, except where f returns a monad.
(My use case is when f randomly selects the next element, i.e. text
generation from markov chains.) So I want

  unfoldM1 :: (Monad m) = ([a] - m a) - [a] - m [a]

My instinct, then, would be to do something like:

  unfoldM1 f l = do
next - f l
rest - unfoldM1 f (next : l)
return (next : rest)

But that, like iRecurse above, doesn't work.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak

Suppose iRecurse looks like this:
  iRecurse = do
x - launchMissiles
r - iRecurse
return 1

As x is never needed, launchMissiles will never execute. It obviously is  
not what is needed.


But in Haskell, standart file input|output is often lazy. It's a  
combination of buffering and special tricks, not the usual rule.


Scott Lawrence byt...@gmail.com писал(а) в своём письме Tue, 31 May 2011  
22:49:02 +0300:



I was under the impression that operations performed in monads (in this
case, the IO monad) were lazy. (Certainly, every time I make the
opposite assumption, my code fails :P .) Which doesn't explain why the
following code fails to terminate:

  iRecurse :: (Num a) = IO a
  iRecurse = do
recurse - iRecurse
return 1

  main = (putStrLn . show) = iRecurse

Any pointers to a good explanation of when the IO monad is lazy?


=== The long story ===

I wrote a function unfold with type signature (([a] - a) - [a]), for
generating a list in which each element can be calculated from all of
the previous elements.

  unfold :: ([a] - a) - [a]
  unfold f = unfold1 f []

  unfold1 :: ([a] - a) - [a] - [a]
  unfold1 f l = f l : unfold1 f (f l : l)

Now I'm attempting to do the same thing, except where f returns a monad.
(My use case is when f randomly selects the next element, i.e. text
generation from markov chains.) So I want

  unfoldM1 :: (Monad m) = ([a] - m a) - [a] - m [a]

My instinct, then, would be to do something like:

  unfoldM1 f l = do
next - f l
rest - unfoldM1 f (next : l)
return (next : rest)

But that, like iRecurse above, doesn't work.


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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
On 05/31/2011 04:20 PM, Artyom Kazak wrote:
 Suppose iRecurse looks like this:
   iRecurse = do
 x - launchMissiles
 r - iRecurse
 return 1
 
 As x is never needed, launchMissiles will never execute. It obviously is
 not what is needed.

Prelude let launchMissiles = putStrLn UH OH  return 1
Prelude let iRecurse = launchMissiles  return 1
Prelude iRecurse
UH OH
1
Prelude

Looks like launchMissiles /does/ execute, even though x is (obviously)
never needed.




signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Anthony Cowley
On Tue, May 31, 2011 at 3:49 PM, Scott Lawrence byt...@gmail.com wrote:
 I was under the impression that operations performed in monads (in this
 case, the IO monad) were lazy. (Certainly, every time I make the
 opposite assumption, my code fails :P .) Which doesn't explain why the
 following code fails to terminate:

  iRecurse :: (Num a) = IO a
  iRecurse = do
    recurse - iRecurse
    return 1

  main = (putStrLn . show) = iRecurse

 Any pointers to a good explanation of when the IO monad is lazy?

import System.IO.Unsafe

iRecurse :: (Num a) = IO a
iRecurse = do
  recurse - unsafeInterleaveIO iRecurse
  return 1

More interesting variations of this leave you with questions of
whether or not the missles were launched, or, worse yet, was data
actually read from the file handle?

Anthony

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Yves Parès
No, I think Artyom meant assuming IO is lazy.
He intended to show that, indeed, it is not, or else side-effects would
never be performed


2011/5/31 Scott Lawrence byt...@gmail.com

 On 05/31/2011 04:20 PM, Artyom Kazak wrote:
  Suppose iRecurse looks like this:
iRecurse = do
  x - launchMissiles
  r - iRecurse
  return 1
 
  As x is never needed, launchMissiles will never execute. It obviously is
  not what is needed.

 Prelude let launchMissiles = putStrLn UH OH  return 1
 Prelude let iRecurse = launchMissiles  return 1
 Prelude iRecurse
 UH OH
 1
 Prelude

 Looks like launchMissiles /does/ execute, even though x is (obviously)
 never needed.



 ___
 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 in Monads

2011-05-31 Thread Artyom Kazak
Scott Lawrence byt...@gmail.com писал(а) в своём письме Tue, 31 May 2011  
23:29:49 +0300:



On 05/31/2011 04:20 PM, Artyom Kazak wrote:

Suppose iRecurse looks like this:
  iRecurse = do
x - launchMissiles
r - iRecurse
return 1

As x is never needed, launchMissiles will never execute. It obviously is
not what is needed.

Prelude let launchMissiles = putStrLn UH OH  return 1
Prelude let iRecurse = launchMissiles  return 1
Prelude iRecurse
UH OH
1
Prelude
Looks like launchMissiles /does/ execute, even though x is (obviously)
never needed.


Oh, sorry. I was unclear. I have meant assuming IO is lazy, as Yves  
wrote.


And saying some hacks I meant unsafeInterleaveIO, which lies beneath the  
laziness of, for example, getContents.


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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Gregory Crosswhite

On 5/31/11 12:49 PM, Scott Lawrence wrote:

I was under the impression that operations performed in monads (in this
case, the IO monad) were lazy.


Whether they are lazy or not depends entirely on the definition of the 
monad.  For example, if you look up the ST and State monads you will 
find that they come in strict and lazy flavors.


As a general rule, operations in the IO monad are strict except for very 
special cases which are explicitly labeled as such, e.g. 
unsafeInterleaveIO, lazyIO, etc.


FYI, in GHC the definition of IO is at


http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-prim-0.2.0.0/src/GHC-Types.html#IO


You can tell it is strict because the result of the map is an unboxed 
tuple, which is strict (at least, if I understand correctly :-) ).


If you are curious, State# and RealWorld are defined here:


http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-prim-0.2.0.0/src/GHC-Prim.html#State.


State# and RealWorld do not contain data constructors because they are 
not intended to contain data but rather to parametrize types --- that is 
to say, you can think of IO as being a special case of the strict ST 
transformer which uses a special type tag to keep different ST threads 
separate (even though this type is never instantiated), and in the case 
of IO the state tag is RealWorld.


So in short, monads need not be strict but often are, and in particular 
IO is designed to be strict because it is essentially just a special 
case of the strict ST monad.


Cheers,
Greg

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
On 05/31/2011 04:48 PM, Artyom Kazak wrote:
 
 Oh, sorry. I was unclear. I have meant assuming IO is lazy, as Yves
 wrote.

Ah, ok. That makes more sense.

 
 And saying some hacks I meant unsafeInterleaveIO, which lies beneath
 the laziness of, for example, getContents.

Which explains why assuming getContents is strict has never worked for me.

I'm trying to implement unfoldM1 without using unsafeIO, if possible. Since

  unfoldM1 f l = do
next - f l
rest - unfoldM1 f (next : l)
return (next : rest)

obviously won't work, I've been trying to use fmap

  unfoldM1 :: (Functor m, Monad m) = ([a] - m a) - [a] - m [a]
  unfoldM1 f l = do
next - f l
fmap (next :) $ unfoldM1 f (next : l)

Evaluation here also doesn't terminate (or, (head $ unfoldM (return .
head)) doesn't), although I can't figure out why. fmap shouldn't need to
fully evaluate a list to prepend an element, right?



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 22:35:26, Yves Parès wrote:
 He intended to show that, indeed, it is not, or else side-effects would
 never be performed

On the other hand, IO is lazy in the values it produces.
Going with the IO a = State RealWorld a fiction, IO is state-strict but 
value-lazy. The side-effects affect the state, hence are performed, the 
values are only evaluated to the extent required to determine the state.

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Stephen Tetley
2011/5/31 Scott Lawrence byt...@gmail.com:

 Evaluation here also doesn't terminate (or, (head $ unfoldM (return .
 head)) doesn't), although I can't figure out why. fmap shouldn't need to
 fully evaluate a list to prepend an element, right?

I'm afriad fmap doesn't get to choose - if the monad is strict then
both definitions are equivalent (probably...).

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
Apparently:

Prelude let r = (fmap (1:) r) :: IO [Integer]
Prelude fmap (take 5) r
*** Exception: stack overflow

Thanks - I'll just have to stay out of IO for this, then.

On Tue, May 31, 2011 at 17:05, Stephen Tetley stephen.tet...@gmail.com wrote:
 2011/5/31 Scott Lawrence byt...@gmail.com:

 Evaluation here also doesn't terminate (or, (head $ unfoldM (return .
 head)) doesn't), although I can't figure out why. fmap shouldn't need to
 fully evaluate a list to prepend an element, right?

 I'm afriad fmap doesn't get to choose - if the monad is strict then
 both definitions are equivalent (probably...).

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




-- 
Scott Lawrence

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Antoine Latter
On Tue, May 31, 2011 at 2:49 PM, Scott Lawrence byt...@gmail.com wrote:
 I was under the impression that operations performed in monads (in this
 case, the IO monad) were lazy. (Certainly, every time I make the
 opposite assumption, my code fails :P .) Which doesn't explain why the
 following code fails to terminate:

  iRecurse :: (Num a) = IO a
  iRecurse = do
    recurse - iRecurse
    return 1

  main = (putStrLn . show) = iRecurse

 Any pointers to a good explanation of when the IO monad is lazy?


 === The long story ===

 I wrote a function unfold with type signature (([a] - a) - [a]), for
 generating a list in which each element can be calculated from all of
 the previous elements.

  unfold :: ([a] - a) - [a]
  unfold f = unfold1 f []

  unfold1 :: ([a] - a) - [a] - [a]
  unfold1 f l = f l : unfold1 f (f l : l)

 Now I'm attempting to do the same thing, except where f returns a monad.
 (My use case is when f randomly selects the next element, i.e. text
 generation from markov chains.) So I want

  unfoldM1 :: (Monad m) = ([a] - m a) - [a] - m [a]

 My instinct, then, would be to do something like:

  unfoldM1 f l = do
    next - f l
    rest - unfoldM1 f (next : l)
    return (next : rest)

 But that, like iRecurse above, doesn't work.


You could use a different type:

 type IOStream a = (a, IO (IOStream a))

 unfold :: ([a] - IO a) - IO (IOStream a)
 unfold f =
 let go prev = do
   next - f prev
   return (next, go (next:prev))
 in do
   z - f []
   go [z]

 toList :: Int - IOStream a - IO [a]
 toList 0 _ = return []
 toList n (x,rest) = do
   xs - toList (n-1) rest
   return (x:xs)

Antoine

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Antoine Latter
On Tue, May 31, 2011 at 6:10 PM, Antoine Latter aslat...@gmail.com wrote:

 You could use a different type:

 type IOStream a = (a, IO (IOStream a))

 unfold :: ([a] - IO a) - IO (IOStream a)
 unfold f =
     let go prev = do
           next - f prev
           return (next, go (next:prev))
     in do
       z - f []
       go [z]

 toList :: Int - IOStream a - IO [a]
 toList 0 _ = return []
 toList n (x,rest) = do
   xs - toList (n-1) rest
   return (x:xs)


Let's pretend I did that right:

 toList :: Int - IOStream a - IO [a]
 toList 0 _ = return []
 toList 1 (x,_) = return [x]
 toList n (x,r) = do
   rest - r
   xs - toList (n-1) rest
   return (x:xs)

Antoine

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


Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Albert Y. C. Lai

On a tangent, not doing IO, but food for thought:

{-# LANGUAGE FlexibleContexts #-}

import Control.Monad.State.Lazy as N
import Control.Monad.State.Strict as S

gen :: (MonadState [()] m) = m ()
gen = do
  gen
  modify (() :)

many = take 3 (N.execState gen [])
none = take 3 (S.execState gen [])


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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Tillmann Rendel

Hi,

Daniel Fischer wrote:

Let's look at the following code:

countdown n = if n == 0 then 0 else foo (n - 1)


s/foo/countdown/

presumably



if' c t e = if c then t else e
countdown' n = if' (n == 0) 0 (foo (n - 1))


s/foo/countdown'/


Yes to both substitutions. Looks like I need an email client with ghc 
integration.


  Tillmann

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Daniel Fischer
On Thursday 17 March 2011 13:05:33, Tillmann Rendel wrote:
 Looks like I need an email client with ghc  integration.

That would be awesome.

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


[Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
Hello,

A question recently popped into my mind: does lazy evaluation reduce the
need to proper tail-recursion?
I mean, for instance :

fmap f [] = []
fmap f (x:xs) = f x : fmap f xs

Here fmap is not tail-recursive, but thanks to the fact that operator (:) is
lazy, I think that it may still run in constant space/time, am I right?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel

Hi,

Yves Parès wrote:

A question recently popped into my mind: does lazy evaluation reduce the
need to proper tail-recursion?
I mean, for instance :

fmap f [] = []
fmap f (x:xs) = f x : fmap f xs

Here fmap is not tail-recursive, but thanks to the fact that operator (:) is
lazy, I think that it may still run in constant space/time, am I right?


In a sense, that definition of fmap is tail-recursive.

To see that, consider how a non-strict list could be encoded in a strict 
language:


  data EvaluatedList a
=  Cons a (List a)
|  Empty

  type List a
= () - EvaluatedList a

  map :: (a - b) - (List a - List b)
  map f xs
= \_ - case xs () of
  Cons x xs  -  Cons (f x) (\_ - map f xs ())
  Empty  -  Empty

Here, the call to map is more visibly in tail position.


So I would say that in Haskell, tail-call optimization is just as 
important as, for example, in Scheme. But tail positions are not defined 
syntactically, but semantically, depending on the strictness properties 
of the program.


  Tillmann

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 18:31:00, Yves Parès wrote:
 Hello,
 
 A question recently popped into my mind: does lazy evaluation reduce the
 need to proper tail-recursion?
 I mean, for instance :
 
 fmap f [] = []
 fmap f (x:xs) = f x : fmap f xs
 
 Here fmap is not tail-recursive, but thanks to the fact that operator
 (:) is lazy, I think that it may still run in constant space/time, am I
 right?

Yes, and a tail-recursive map couldn't run in constant space, as far as I 
can see (time is O(length) for both of course, if the result is compeltely 
consumed).

Tail recursion is good for strict stuff, otherwise the above pattern - I 
think it's called guarded recursion - is better, have the recursive call as 
a non-strict field of a constructor.

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
 Yes, and a tail-recursive map couldn't run in constant space

Yes, I meant if you are consuming it just once immediately.

 the above pattern [...] is better, have the recursive call as a non-strict
field of a constructor.

Which pattern? Mine or Tillman's? Or both?

2011/3/16 Daniel Fischer daniel.is.fisc...@googlemail.com

 On Wednesday 16 March 2011 18:31:00, Yves Parès wrote:
  Hello,
 
  A question recently popped into my mind: does lazy evaluation reduce the
  need to proper tail-recursion?
  I mean, for instance :
 
  fmap f [] = []
  fmap f (x:xs) = f x : fmap f xs
 
  Here fmap is not tail-recursive, but thanks to the fact that operator
  (:) is lazy, I think that it may still run in constant space/time, am I
  right?

 Yes, and a tail-recursive map couldn't run in constant space, as far as I
 can see (time is O(length) for both of course, if the result is compeltely
 consumed).

 Tail recursion is good for strict stuff, otherwise the above pattern - I
 think it's called guarded recursion - is better, have the recursive call as
 a non-strict field of a constructor.

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Henning Thielemann


On Wed, 16 Mar 2011, Daniel Fischer wrote:

Tail recursion is good for strict stuff, otherwise the above pattern - I 
think it's called guarded recursion - is better, have the recursive call as 
a non-strict field of a constructor.


In
  http://haskell.org/haskellwiki/Tail_recursion
 it is also called 'guarded recursion', however the linked article is yet 
to be written ...


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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 20:02:54, Yves Parès wrote:
  Yes, and a tail-recursive map couldn't run in constant space
 
 Yes, I meant if you are consuming it just once immediately.
 

And that's what, to my knowledge, is impossible with tail recursion. A tail 
recursive map/fmap would have to traverse the entire list before it could 
return anything.

  the above pattern [...] is better, have the recursive call as a
  non-strict
 
 field of a constructor.
 
 Which pattern? Mine or Tillman's? Or both?

Yours/the Prelude's. I hadn't seen Tillmann's reply yet when I wrote mine.
In

map f (x:xs) = (:) (f x) (map f xs)

the outermost call is a call to a constructor [that is not important, it 
could be a call to any sufficiently lazy function, so that you have a 
partial result without traversing the entire list] which is lazy in both 
fields, so a partial result is returned immediately. If the element (f x) 
or the tail is not needed, it won't be evaluated at all.
If there are no other references, the (f x) can be garbage collected 
immediately after being consumed/ignored.


Tillmann:

   data EvaluatedList a
   
  =  Cons a (List a)
  
  |  Empty

type List a

  = () - EvaluatedList a

map :: (a - b) - (List a - List b)
map f xs

  = \_ - case xs () of
  
Cons x xs  -  Cons (f x) (\_ - map f xs ())
Empty  -  Empty
 
 Here, the call to map is more visibly in tail position.

According to the definition of tail recursion that I know, that's not tail 
recursive.
By that, a function is tail-recursive if the recursive call (if there is 
one) is the last thing the function does, which in Haskell would translate 
to it being the outermost call.

Thus a tail recursive map would be

map some args (x:xs) = map other args' xs

, with a worker:

map f  = go []
  where
go ys [] = reverse ys
go ys (x:xs) = go (f x:ys) xs

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel

Hi,

Daniel Fischer wrote:

   data EvaluatedList a

  =  Cons a (List a)

  |  Empty

type List a

  = () -  EvaluatedList a

map :: (a -  b) -  (List a -  List b)
map f xs

  = \_ -  case xs () of

Cons x xs  -   Cons (f x) (\_ -  map f xs ())
Empty  -   Empty

Here, the call to map is more visibly in tail position.


According to the definition of tail recursion that I know, that's not tail
recursive.


My point is that the call to map is in tail position, because it is  
the last thing the function (\_ - map f xs ()) does. So it is not a  
tail-recursive call, but it is a tail call.


Of course, (\_ - map f xs ()) does not occur literally in the Haskell  
implementation of map, but the runtime behavior of the Haskell  
implementation of map is similar to the runtime behavior of the code  
above in a strict language.



Let's look at the following code:

  countdown n = if n == 0 then 0 else foo (n - 1)

  if' c t e = if c then t else e
  countdown' n = if' (n == 0) 0 (foo (n - 1))

countdown is clearly tail-recursive. Because of Haskell's non-strict  
semantics, countdown and countdown' have the same runtime behavior. I  
therefore submit that countdown' is tail-recursive, too.



So I think that in a non-strict language like Haskell, we need to  
define tail position semantically, not syntactically.


  Tillmann


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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
  And that's what, to my knowledge, is impossible with tail recursion. A
tail
 recursive map/fmap would have to traverse the entire list before it could
return anything.

Now that you say it, yes, you are right. Tail recursion imposes strictness,
since only the very last call can return something.

Can a type signature give you a hint about whether a function evaluates
some/all of its arguments (i.e. is strict/partially strict/lazy), or do you
have to look at the implementation to know?


2011/3/16 Daniel Fischer daniel.is.fisc...@googlemail.com

 On Wednesday 16 March 2011 20:02:54, Yves Parès wrote:
   Yes, and a tail-recursive map couldn't run in constant space
 
  Yes, I meant if you are consuming it just once immediately.
 

 And that's what, to my knowledge, is impossible with tail recursion. A tail
 recursive map/fmap would have to traverse the entire list before it could
 return anything.

   the above pattern [...] is better, have the recursive call as a
   non-strict
 
  field of a constructor.
 
  Which pattern? Mine or Tillman's? Or both?

 Yours/the Prelude's. I hadn't seen Tillmann's reply yet when I wrote mine.
 In

 map f (x:xs) = (:) (f x) (map f xs)

 the outermost call is a call to a constructor [that is not important, it
 could be a call to any sufficiently lazy function, so that you have a
 partial result without traversing the entire list] which is lazy in both
 fields, so a partial result is returned immediately. If the element (f x)
 or the tail is not needed, it won't be evaluated at all.
 If there are no other references, the (f x) can be garbage collected
 immediately after being consumed/ignored.


 Tillmann:

data EvaluatedList a
 
   =  Cons a (List a)
 
   |  Empty
 
 type List a
 
   = () - EvaluatedList a
 
 map :: (a - b) - (List a - List b)
 map f xs
 
   = \_ - case xs () of
 
 Cons x xs  -  Cons (f x) (\_ - map f xs ())
 Empty  -  Empty
 
  Here, the call to map is more visibly in tail position.

 According to the definition of tail recursion that I know, that's not tail
 recursive.
 By that, a function is tail-recursive if the recursive call (if there is
 one) is the last thing the function does, which in Haskell would translate
 to it being the outermost call.

 Thus a tail recursive map would be

 map some args (x:xs) = map other args' xs

 , with a worker:

 map f  = go []
  where
go ys [] = reverse ys
go ys (x:xs) = go (f x:ys) xs

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 21:44:36, Tillmann Rendel wrote:
 My point is that the call to map is in tail position, because it is  
 the last thing the function (\_ - map f xs ()) does. So it is not a  
 tail-recursive call, but it is a tail call.

Mmmm, okay, minor terminology mismatch, then. Makes sense, but is not what 
I'm used to. I'd say it is a tail-call of Cons's second argument, and the 
tail call of map would be Cons, so tail-call is not transitive.

 
 Of course, (\_ - map f xs ()) does not occur literally in the Haskell  
 implementation of map, but the runtime behavior of the Haskell  
 implementation of map is similar to the runtime behavior of the code  
 above in a strict language.
 
 
 Let's look at the following code:
 
countdown n = if n == 0 then 0 else foo (n - 1)

s/foo/countdown/

presumably

 
if' c t e = if c then t else e
countdown' n = if' (n == 0) 0 (foo (n - 1))

s/foo/countdown'/

 
 countdown is clearly tail-recursive. Because of Haskell's non-strict  
 semantics, countdown and countdown' have the same runtime behavior. I  
 therefore submit that countdown' is tail-recursive, too.
 

Formally, not according to the previously mentioned definition, but in 
terms of generated code/runtime behaviour, of course, so

 
 So I think that in a non-strict language like Haskell, we need to  
 define tail position semantically, not syntactically.

I think you're right.

 
Tillmann

Cheers,
Daniel

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


Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 22:03:51, Yves Parès wrote:
 Can a type signature give you a hint about whether a function evaluates
 some/all of its arguments (i.e. is strict/partially strict/lazy), or do
 you have to look at the implementation to know?

Cheating, with GHC, a magic hash tells you it's strict (

foo :: Int# - Double# - Double

). But generally, a type signature can give at most a hint, because the 
implementation could always be

foo _ = undefined-- [], Nothing, 0, whatever the result type supports

and hints for laziness tend to be stronger than hints for strictness (

const :: a - b - a

hints strongly that it's lazy in the second argument, but it could still be 
strict; arguments of type Int, Double or the like have a better than 
average chance of being strict).

The only way to know is looking at the implementation, but if the docs say 
something about strictness, that should be good enough unless you have 
reason to suspect they're wrong.

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


[Haskell-cafe] Lazy evaluation from Why Functional programming matters

2010-10-05 Thread C K Kashyap
Hi All,

I was going through the paper's lazy evaluation section where the
square root example is given. It occurred to me that one could
implement it in a modular way with just higher order functions
(without the need for lazy evaluation that is).


function f (within, eps, next, a0){
   while(true){
a1=next(a0);
if(within(a0,a1,eps)return a0;
   a0=a1;
   }
}

Is this not the case?

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


Re: [Haskell-cafe] Lazy evaluation from Why Functional programming matters

2010-10-05 Thread Hemanth Kapila
Hi,

Let us try to rewrite the code in a more java-esque syntax:

It translates to something like the below generic method. Correct?

static T T function(IBoundsCheckT within, DeltaT eps,  IteratorT
iterator, T initValue){
  T currVal = initVal;
while(iterator.hasNext()){
T nextVal = iterator.next();
 if(within.verify(delta, eps, currVal, nextVal))
  return currVal;
 currVal = nextVal
   }
}


I have not tested it but I think this is a fair translation of the code.
 (For instance, by using an appropriate implementation of IBoundsCheck, I
will be able to implement the 'relativeSqrt' functionality of the example).

But this IS still a lazy evaluation. By passing an iterator instead of a
list as the third argument of the static method, I achieved 'laziness'.

In the example, the laziness is in the way we are iterating over the
sequence of values [a0,f(a0), f(f(a0)),...] and so on and not on when the
runtime evaluates appropriate values.

Just that having to write,

(repeat (next N) a0)

is (take 1000 (repeat 1)) times more intuitive and convenient than having to
implement the Iterator for T or implementing a true-while loop.


/Hemanth K



On Tue, Oct 5, 2010 at 4:50 PM, C K Kashyap ckkash...@gmail.com wrote:

 Hi All,

 I was going through the paper's lazy evaluation section where the
 square root example is given. It occurred to me that one could
 implement it in a modular way with just higher order functions
 (without the need for lazy evaluation that is).


 function f (within, eps, next, a0){
   while(true){
a1=next(a0);
if(within(a0,a1,eps)return a0;
   a0=a1;
   }
 }

 Is this not the case?

 --
 Regards,
 Kashyap
 ___
 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 from Why Functional programming matters

2010-10-05 Thread C K Kashyap
 Hi,
 Let us try to rewrite the code in a more java-esque syntax:
 It translates to something like the below generic method. Correct?
 static T T function(IBoundsCheckT within, DeltaT eps,  IteratorT
 iterator, T initValue){
       T currVal = initVal;
     while(iterator.hasNext()){
         T nextVal = iterator.next();
          if(within.verify(delta, eps, currVal, nextVal))
                           return currVal;
          currVal = nextVal
    }
 }

 I have not tested it but I think this is a fair translation of the code.
  (For instance, by using an appropriate implementation of IBoundsCheck, I
 will be able to implement the 'relativeSqrt' functionality of the example).
 But this IS still a lazy evaluation. By passing an iterator instead of a
 list as the third argument of the static method, I achieved 'laziness'.
 In the example, the laziness is in the way we are iterating over the
 sequence of values [a0,f(a0), f(f(a0)),...] and so on and not on when the
 runtime evaluates appropriate values.
 Just that having to write,
 (repeat (next N) a0)
 is (take 1000 (repeat 1)) times more intuitive and convenient than having to
 implement the Iterator for T or implementing a true-while loop.

I see ... I think I understand now.
hmmm ... I am little disappointed though - does that mean that all
the laziness cool stuffs can actually be done using
iterators(generators)?
As in, but for the inconvenient syntax, you can do it all in - say java?

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


Re: [Haskell-cafe] Lazy evaluation from Why Functional programming matters

2010-10-05 Thread Brent Yorgey
On Tue, Oct 05, 2010 at 07:37:32PM +0530, C K Kashyap wrote:
  Hi,
  Let us try to rewrite the code in a more java-esque syntax:
  It translates to something like the below generic method. Correct?
  static T T function(IBoundsCheckT within, DeltaT eps,  IteratorT
  iterator, T initValue){
        T currVal = initVal;
      while(iterator.hasNext()){
          T nextVal = iterator.next();
           if(within.verify(delta, eps, currVal, nextVal))
                            return currVal;
           currVal = nextVal
     }
  }
 
  I have not tested it but I think this is a fair translation of the code.
   (For instance, by using an appropriate implementation of IBoundsCheck, I
  will be able to implement the 'relativeSqrt' functionality of the example).
  But this IS still a lazy evaluation. By passing an iterator instead of a
  list as the third argument of the static method, I achieved 'laziness'.
  In the example, the laziness is in the way we are iterating over the
  sequence of values [a0,f(a0), f(f(a0)),...] and so on and not on when the
  runtime evaluates appropriate values.
  Just that having to write,
  (repeat (next N) a0)
  is (take 1000 (repeat 1)) times more intuitive and convenient than having to
  implement the Iterator for T or implementing a true-while loop.
 
 I see ... I think I understand now.
 hmmm ... I am little disappointed though - does that mean that all
 the laziness cool stuffs can actually be done using
 iterators(generators)?
 As in, but for the inconvenient syntax, you can do it all in - say
 java?

You can do anything in any Turing-complete language, but for the
inconvenient syntax.  So what?

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


Re: [Haskell-cafe] Lazy evaluation from Why Functional programming matters

2010-10-05 Thread Hemanth Kapila

 I see ... I think I understand now.
 hmmm ... I am little disappointed though - does that mean that all
 the laziness cool stuffs can actually be done using
 iterators(generators)?
 As in, but for the inconvenient syntax, you can do it all in - say java?


Yes. It would slightly easier in, say,  C# or C++.
I think 'D' achieves its implementation of the 'lazy' keyword using a
similar approach.

But I did not understand why you are disappointed ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy evaluation from Why Functional programming matters

2010-10-05 Thread C K Kashyap

 Yes. It would slightly easier in, say,  C# or C++.
 I think 'D' achieves its implementation of the 'lazy' keyword using a
 similar approach.
 But I did not understand why you are disappointed ?

The disappointment was not on a serious note ... the thing is, I
constantly run into discussions
about why fp with my colleagues - in a few of such discussions, I
had mentioned that Haskell is the
only well known language with lazy evaluation (IIRC, I read it
somewhere or heard it in one of the videos)

And I had built up this impression that laziness distinguished Haskell
by a huge margin ... but it seems that is not the case.
Hence the disappointment.


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


Re: [Haskell-cafe] Lazy evaluation from Why Functional programming matters

2010-10-05 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 10/5/10 10:52 , C K Kashyap wrote:
 And I had built up this impression that laziness distinguished Haskell
 by a huge margin ... but it seems that is not the case.
 Hence the disappointment.

Haskell is lazy-by-default and designed around lazy evaluation, whereas most
other languages are strict by default, designed around strictness, and make
you do extra work to get laziness which you then may lose rather easily.
Sometimes it's as easy as using an iterator, other times it means passing
around closures and invoking them at just the right time.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkyrVcgACgkQIn7hlCsL25W5tQCeMoY6XCcDLKFh3tbwdrliQSqd
grcAnjCGqxBwRsEoI2pG3+ZgA4biSDAw
=kgwK
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Lazy evaluation/functions

2009-12-27 Thread michael rice
I've seen the terms lazy evaluation and lazy function. Is this just lazy 
language or are both these terms valid?

Michael



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


Re: [Haskell-cafe] Lazy evaluation/functions

2009-12-27 Thread Tom Davie
Lazy evaluation is an evaluation strategy that gives non-strict semantics.

A lazy function I'm not sure how to define.  It may be lazy language meaning
a function which is non-strict in one of it's arguments.

Bob

On Sun, Dec 27, 2009 at 1:16 PM, michael rice nowg...@yahoo.com wrote:

 I've seen the terms lazy evaluation and lazy function. Is this just
 lazy language or are both these terms valid?

 Michael


 ___
 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/functions

2009-12-27 Thread Erlend Hamberg
On Sunday 27. December 2009 14.16.15 michael rice wrote:
 I've seen the terms lazy evaluation and lazy function. Is this just
  lazy language or are both these terms valid?

In some languages, like Oz, one can have lazy functions even though the 
default is evaluation strategy is an eager one. In cases like that it is 
convenient to call those functions “lazy functions”.
-- 
Erlend Hamberg
Everything will be ok in the end. If its not ok, its not the end.
GPG/PGP:  0xAD3BCF19
45C3 E2E7 86CA ADB7 8DAD 51E7 3A1A F085 AD3B CF19


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


[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


[Haskell-cafe] lazy evaluation

2008-02-06 Thread Peter Padawitz
Can anybody give me a simple explanation why the second definition of a 
palindrome checker does not terminate, although the first one does?


pal :: Eq a = [a] - Bool
pal s = b where (b,r) = eqrev s r []

eqrev :: Eq a = [a] - [a] - [a] - (Bool,[a])
eqrev (x:s1) ~(y:s2) acc = (x==yb,r) where (b,r) = eqrev s1 s2 (x:acc)
eqrev _ _ acc  = (True,acc)

pal :: Eq a = [a] - Bool
pal s = b where (b,r) = eqrev' s r

eqrev' :: Eq a = [a] - [a] - (Bool,[a])
eqrev' (x:s1) ~(y:s2) = (x==yb,r++[y]) where (b,r) = eqrev' s1 s2
eqrev' _ _   = (True,[])

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


Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Henning Thielemann

On Wed, 6 Feb 2008, Peter Padawitz wrote:

 Can anybody give me a simple explanation why the second definition of a
 palindrome checker does not terminate, although the first one does?

Just another question, what about
   x == reverse x
 ? - You can still optimize for avoiding duplicate equality tests.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Josef Svenningsson
On Feb 6, 2008 3:06 PM, Miguel Mitrofanov [EMAIL PROTECTED] wrote:

 On 6 Feb 2008, at 16:32, Peter Padawitz wrote:

  Can anybody give me a simple explanation why the second definition
  of a palindrome checker does not terminate, although the first one
  does?
 
  pal :: Eq a = [a] - Bool
  pal s = b where (b,r) = eqrev s r []
 
  eqrev :: Eq a = [a] - [a] - [a] - (Bool,[a])
  eqrev (x:s1) ~(y:s2) acc = (x==yb,r) where (b,r) = eqrev s1 s2
  (x:acc)
  eqrev _ _ acc  = (True,acc)

 I.eqrev  (_|_) acc = (True, acc)
 II.a. eqrev 1 (_|_)  = ('1' == (_|_)  b, r) where (b,r) = eqrev
  (_|_) 1
By (I), (b,r) = (True, 1), so eqrev 1 (_|_)  = ((_|_),1)
 II.b. eqrev 1 1  = ('1' == '1'  b, r) where (b,r) = eqrev 
  1
(b,r) = (True,1), so eqrev 1 1  = (True,1)

 Therefore, the least fixed point of \r - eqrev 1 r  is 1 and
 the answer is True.

  pal :: Eq a = [a] - Bool
  pal s = b where (b,r) = eqrev' s r
 
  eqrev' :: Eq a = [a] - [a] - (Bool,[a])
  eqrev' (x:s1) ~(y:s2) = (x==yb,r++[y]) where (b,r) = eqrev' s1 s2
  eqrev' _ _   = (True,[])

 I.  eqrev'  (_|_) = (True,[])
 II.a. eqrev' 1 (_|_) = ('1' == (_|_)  b, r ++ [(_|_)]) where (b,r)
 = eqrev'  (_|_)
By (I), (b,r) = (True,[]), so eqrev' 1 (_|_) = ((_|_),[(_|_)])
 II.b. eqrev' 1 [(_|_)] = ('1' == (_|_)  b, r ++ [(_|_)]) where
 (b,r) = eqrev'  []
(b,r) = (True,[]), so eqrev' 1 [(_|_)] = ((_|_),[(_|_)])
 Therefore, the least fixed point of \r - eqrev' 1 r is [(_|_)] and
 the answer is (_|_). No wonder it hangs.

This proof also shows us where the problem lies and how to fix it. It
turns out to be really easy: change 'r++[y]' to 'r++[x]' and the
program works.

Cheers,

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