
Hello, guys. Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works. The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks. To tell you the truth, I don't know how laziness works in general in haskell. Can someone help me understand how it works in this example, and give some pointers to materials on the subject? The "tying the knot" article on the wiki is pretty mind bending too. -- | @'forever' act@ repeats the action infinitely. forever :: (Monad m) => m a -> m b {-# INLINE forever #-}forever a = let a' = a >> a' in a' -- Eduardo Sato

The way forever is implemented is a bit obtuse. It's mainly a hack to make
GHC's optimizer avoid space leaking no matter what the surrounding code is.
You can think of the implementation as just:
forever :: Monad m => m a -> m b
forever act = do
act
forever act
which is pretty much what you'd do in an imperative language, so it's not
that crazy.
You can see the similarity if you replace the do notation with manual binds
and rename 'act' to 'a':
forever :: Monad m => m a -> m b
forever a = a >> forever a
Again, the knot tying stuff is just to prevent a space leak in certain
optimization scenarios.
On Mon, Dec 23, 2013 at 9:02 PM, Eduardo Sato
Hello, guys.
Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works.
The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks.
To tell you the truth, I don't know how laziness works in general in haskell.
Can someone help me understand how it works in this example, and give some pointers to materials on the subject?
The "tying the knot" article on the wiki is pretty mind bending too.
-- | @'forever' act@ repeats the action infinitely.
forever :: (Monad m) => m a -> m b
{-# INLINE forever #-}forever a = let a' = a >> a' in a'
--
Eduardo Sato
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907

On Tuesday, December 24, 2013, Clark Gaebel wrote:
forever :: Monad m => m a -> m b forever a = a >> forever a
Thanks for your response. This is actually how I would have implemented it. What is confusing to me is the recursion on the let construct. What is not clear to me is when we can "get away" with doing that kind of thing. I mentioned the "tying the knot article" because it, too, uses recursion on a let construct. -- Eduardo Sato

What is confusing to me is the recursion on the let construct. Oh sry I may have misunderstood your question then.
You can think of defining 'forever' itself as a let construct. Starting
from the "simpler" implementation:
let forever a = a >> forever a
Now let's just give the rhs another name, again using 'let':
let forever a = (let a' = a >> forever a in a')
But we can see that a' is actually equal to (forever a), so we can replace
on in the rhs:
let forever a = (let a' = a >> a' in a')
There is no trickery, no getting away, this recursion is the same as what
you have thought of:)
On 24 December 2013 02:46, Eduardo Sato
On Tuesday, December 24, 2013, Clark Gaebel wrote:
forever :: Monad m => m a -> m b forever a = a >> forever a
Thanks for your response. This is actually how I would have implemented it.
What is confusing to me is the recursion on the let construct.
What is not clear to me is when we can "get away" with doing that kind of thing. I mentioned the "tying the knot article" because it, too, uses recursion on a let construct.
-- Eduardo Sato
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

In order to understand laziness in Haskell we first need to look at what WHNF (= Weak Head Normal Form) means: http://stackoverflow.com/questions/6872898/haskell-what-is-weak-head-normal-... Then the only rule you have to remember is that a reduction step (to whnf) only occurs in Haskell when: 1. Evaluating a case expression (pattern matching) 2. Evaluating a seq expression (this is irrelevant for now) Your example is a bit tricky as we don't have a concrete monad to work with. For some monads pattern matching on a (forever something) will loop forever, for some it may terminate. An example for the first one is the Identity monad: Identity a >>= f = f a Trying to reduce (forever (Identity x)) will go something like this: (formally these are not all reducion steps but this is how I unroll the expression in my head) forever (Identity x) let a' = Identity x >> a' in a' Identity x >> (let a' = X >> a' in a') Identity x >>= (\_ -> let a' = Identity x >> a' in a') (\_ -> let a' = Identity x >> a' in a') x -- this step was the only true reduction let a' = X >> a' in a' And we start looping. An example for a terminating one would be the Either () monad: Left () >>= _ = Left () Right a >>= f = f a And the reduction of the term (forever (Left ()): forever (Left ()) let a' = Left () >> a' in a' Left () >> (let a' = Left () >> a' in a') Left () >>= (\_ -> let a' = Left () >> a' in a') Left () The key step is the last one, reducing Left () >>= (\_ -> let a' = Left ()
a' in a') to whnf resulted in Left (), "short circuiting" the loop.
If you want to understand the theoretical basis of lazy evaluation I
suggest looking into the lambda calculus and different reduction strategies
of it. There is a neat theorem I forgot the name of that shows why lazy
evaluation is the "right" one in the sense that if a term T reduces to
another term T' using any evaluation strategy then it will also reduce to
T' using lazy evaluation.
On 24 December 2013 02:02, Eduardo Sato
Hello, guys.
Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works.
The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks.
To tell you the truth, I don't know how laziness works in general in haskell.
Can someone help me understand how it works in this example, and give some pointers to materials on the subject?
The "tying the knot" article on the wiki is pretty mind bending too.
-- | @'forever' act@ repeats the action infinitely.
forever :: (Monad m) => m a -> m b
{-# INLINE forever #-}forever a = let a' = a >> a' in a'
--
Eduardo Sato
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The best explanation I've found for how Haskell's evaluation works is here: http://chimera.labs.oreilly.com/books/1230000000929/ch02.html#sec_par-eval-w... On Monday, December 23, 2013, Eduardo Sato wrote:
Hello, guys.
Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works.
The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks.
To tell you the truth, I don't know how laziness works in general in haskell.
Can someone help me understand how it works in this example, and give some pointers to materials on the subject?
The "tying the knot" article on the wiki is pretty mind bending too.
-- | @'forever' act@ repeats the action infinitely.
forever :: (Monad m) => m a -> m b
{-# INLINE forever #-}forever a = let a' = a >> a' in a'
--
Eduardo Sato

On 13-12-23 09:02 PM, Eduardo Sato wrote:
The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks.
To tell you the truth, I don't know how laziness works in general in haskell.
For lazy evaluation, see my http://www.vex.net/~trebla/haskell/lazy.xhtml The following produces and destroys 10 cons cells. Unless the compiler does smart things. main = print (take 10 (plenty 5)) plenty n = n : plenty n The following produces and reuses 1 cons cell. main = print (take 10 (plenty 5)) plenty n = s where s = n : s -- or, let s = n : s in s Reusing comes from sharing. Sharing comes from aliasing. Aliasing is using the same name s. Self-aliasing is then using the same name s on both sides of =. It is best to draw some diagrams. I am too lazy to do it here. But I did some in my lazy evaluation article, and it shows you how to do more on your own. forever is similar.
The "tying the knot" article on the wiki is pretty mind bending too.
Most authors on the haskell wiki are driven by excitement. The problem with excitement is that excited authors lose readers by telling too much and starting too high.
participants (5)
-
Albert Y. C. Lai
-
Andras Slemmer
-
Bob Ippolito
-
Clark Gaebel
-
Eduardo Sato