Re: [Haskell-cafe] The C Equiv of != in Haskell (Apologies)

However, I don't think these other individuals had any business poking their hooters into this.
If you don't want other individuals "poking their hooters" in what you write, I recommend you to avoid sending open questions to public mailing lists. yes, I was indeed referring to you and your large beak over which you clearly have no control. Nobody invited you to this discussion and as you can see I have already apologized to Neil for the misunderstanding. Yet, you seem to be desperate to keep the thread alive.
Uh, save me from the ...

This thread should end, guys. It is inappropriate for the Haskell lists, and appears to have been a simple misunderstanding anyway. Thanks everyone. Please stay friendly! -- Don P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1)

P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
Cute! But what an un-cute qualified name: :t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a -> a) -> a Has nothing to do with monads, and would perhaps be considered as ``out of Control'' in any case... ;-) Wolfram

kahl:
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
Cute!
But what an un-cute qualified name:
:t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a -> a) -> a
Has nothing to do with monads, and would perhaps be considered as ``out of Control'' in any case...
I see it has moved into Data.Function, module Data.Function ( -- * "Prelude" re-exports id, const, (.), flip, ($) -- * Other combinators , fix , on ) where A much better place. -- Don

Donald Bruce Stewart wrote:
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
this is cute indeed! (do you keep an emergency reserve of those around for situations like this? ;-)) ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm not the only one [1]), though a little digging turned up two very nice links, which might be interesting for those who share my situation (hence this post). namely, an old LtU thread [2], in which you will find a short oleg-post [3] (i'd give it about a hundred milli-olegs), and a paper on practical applications of Y [4]. it seems that the examples given in the latter two (scheme and ML) are essentially trivial to translate to haskell, so with the help of ghci, i suppose i will finally get a grip on Y. ;-) either way, if one of the Masters Of The Shadow Y Style on this list feels like throwing in another koan or two, you'll have at least one thankful audience member ;-) kind regards, v. [1] http://www.haskell.org/pipermail/haskell-cafe/2007-March/023662.html [2] http://lambda-the-ultimate.org/classic/message5463.html [3] http://okmij.org/ftp/Computation/overriding-selfapplication.html [4] http://citeseer.ist.psu.edu/mcadams01practical.html

On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote:
Donald Bruce Stewart wrote:
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
this is cute indeed! (do you keep an emergency reserve of those around for situations like this? ;-))
ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm not the only one [1])
The above code is equivalent to let l = 1 : scanl (+) 1 l in l which is a bit easier to decipher. The rest is maths and the subtleties of lazy evaluation. Best regards Tomek

On Tue, May 29, 2007 at 02:19:31PM +0200, Tomasz Zielonka wrote:
On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote:
ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm not the only one [1])
The above code is equivalent to
let l = 1 : scanl (+) 1 l in l
which is a bit easier to decipher.
The rest is maths and the subtleties of lazy evaluation. ... and these are the things you need to focus on to understand this code. In this case the use of fix is almost a small syntactic issue - you can eliminate it by inlining its definition.
Best regards Tomek

Tomasz Zielonka wrote:
On Tue, May 29, 2007 at 02:19:31PM +0200, Tomasz Zielonka wrote:
On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote:
ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm not the only one [1])
The above code is equivalent to
let l = 1 : scanl (+) 1 l in l
which is a bit easier to decipher.
The rest is maths and the subtleties of lazy evaluation.
... and these are the things you need to focus on to understand this code. In this case the use of fix is almost a small syntactic issue - you can eliminate it by inlining its definition.
Best regards Tomek
i see that the definition of fix (from Control.Monad.Fix) could not be any simpler:
fix f = let x = f x in x
same goes for the type: Prelude> :t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a -> a) -> a it's just that i find it difficult to get concrete intellectual mileage out of it. i can reproduce results for specific examples (and even manipulate them a bit), but feel like i'm missing something deep yet simple. say, i would not know where and how to apply it. so obviously true understanding is still missing. reminds me of my first encounters with $H \psi = E \psi$. ;-) most likely, i should just more carefully read the references i cited myself ;-) anyhow. if someone has a "pedestrian's guide to the fixed point operator" lying around, a link would be much appreciated. kind regards, v.

Vincent Kraeutler wrote:
Tomasz Zielonka wrote:
[snip]
anyhow. if someone has a "pedestrian's guide to the fixed point operator" lying around, a link would be much appreciated.
i see that dons has very recently provided an answer for this on reddit: http://programming.reddit.com/info/1uabt/comments eternally indebted, v.

vincent:
i see that the definition of fix (from Control.Monad.Fix) could not be any simpler:
fix f = let x = f x in x
same goes for the type:
Prelude> :t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a -> a) -> a
it's just that i find it difficult to get concrete intellectual mileage out of it. i can reproduce results for specific examples (and even manipulate them a bit), but feel like i'm missing something deep yet simple. say, i would not know where and how to apply it. so obviously true understanding is still missing. reminds me of my first encounters with $H \psi = E \psi$. ;-)
most likely, i should just more carefully read the references i cited myself ;-)
anyhow. if someone has a "pedestrian's guide to the fixed point operator" lying around, a link would be much appreciated.
I use it when I need a local loop expression, maybe once every couple of months. A real world example from xmonad, f = fix $ \again -> do more <- checkMaskEvent d enterWindowMask ev when more again That is, keep sucking up X events till there's no 'more'. Of course, you can always just name your loop with 'where' and use that. f = go where go = do more <- checkMaskEvent d enterWindowMask ev when more go TMTOWTDI with recursion :-) -- Don

Donald Bruce Stewart wrote:
I use it when I need a local loop expression, maybe once every couple of months. A real world example from xmonad,
f = fix $ \again -> do more <- checkMaskEvent d enterWindowMask ev when more again
That is, keep sucking up X events till there's no 'more'.
My God... that's almost as cute as the first thing!

On 29/05/07, Vincent Kraeutler
anyhow. if someone has a "pedestrian's guide to the fixed point operator" lying around, a link would be much appreciated.
Here's a paraphrased quotation from Pierce's "Types and Programming Languages": Suppose we want to write a recursive function definition of the form h = (body containing h) -- i.e., we want to write a definition where the term on the right-hand side of the = uses the very function that we are defining. The intention is that the recursive definition should be "unrolled" at the point where it occurs; for example, the definition of factorial would intuitively be if n=0 then 1 else n * (if n-1=0 then 1 else (n-1) * (if n-2=0 then 1 else (n-2) * ...)) This affect can be achieved using the fix combinator by first defining g = \f. (body containing f) and then h = fix g. For example, we can define the factorial function be g = \fct n. if n == 0 then 1 else n * (fct (n-1)) factorial = fix g Figure 5-2 shows what happens to the term factorial 3 during evaluation: factorial 3 fix g 3 g (fix g) 3 -- Using fix f = f (fix f) if 3 == 0 then 1 else 3 * (fix g 2) -- Using the definition of g 3 * (fix g 2) 3 * (g (fix g) 2) 3 * (if 2 == 0 then 1 else 2 * (fix g 1)) 3 * (2 * (fix g 1)) 3 * (2 * (g (fix g) 1)) 3 * (2 * (if 1 == 0 then 1 else 1 * (fix g 0))) 3 * (2 * (1 * (fix g 0)) 3 * (2 * (1 * (g (fix g) 0))) 3 * (2 * (1 * (if 0 == 0 then 1 else 0 * (fix g -1)))) 3 * (2 * (1 * 1))) 6 The key fact that makes this calculation work is that fix g n evaluates to g (fix g) n. That is, fix g is a kind of "self-replicator" that, when applied to an argument, supplies _itself_ and n as arguments to g. Wherever the first argument appears in the body of g, we will get another copy of fix g, which, when applied to an argument, will again pass itself and that argument to g, etc. Each time we make a recursive call using fix g, we unroll one more copy of the body of g and equip it with new copies of fix g that are ready to do the unrolling again. (Adapted from pp59-60, Types and Programming Languages, Benjamin C. Pierce.) -- -David House, dmhouse@gmail.com

From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Vincent Kraeutler
anyhow. if someone has a "pedestrian's guide to the fixed point operator" lying around, a link would be much appreciated.
Just to add to the noise... I've always quite liked Richard Gabriel's "The Why of Y" essay: http://www.dreamsongs.com/Files/WhyOfY.pdf Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

Vincent Kraeutler
anyhow. if someone has a "pedestrian's guide to the fixed point operator" lying around, a link would be much appreciated.
At the risk of increasing rather than decreasing your confusion (but in the hope that once you get over it you will be enlightened), here's another approach to the subject: Suppose we have a language (either untyped or cleverly typed -- the following won't typecheck in Haskell, but there are ways around it) that allows non-recursive definitions only. We want to define factorial, but it needs to call itself. How about we try to define a function that /when applied to itself/ is factorial? half_fact me n = if n <= 1 then 1 else n * ????? (n-1) ^ | what goes here? Well, we know that we are trying to arrange that half_fact half_fact == factorial so when we use it, the "me" parameter is going to be half_fact, which implies that (me me) will be (half_fact half_fact), which is factorial. So we write: half_fact me n = if n <= 1 then 1 else n * me me (n-1) factorial = half_fact half_fact Now, in such a language we might write all our recursive functions that way, or we might prefer not to have to double up the names to get recursion, and abstract away the operator that ties the knot: define a function that, given the factorial function makes a step of the evaluation and then lets factorial do the rest: step_towards_factorial factorial n = if n <=1 then 1 else n * factorial (n-1) put stf = step_towards_factorial and observe that stf (error "too deep") 1 == 1 stf (stf (error "too deep")) 2 == 2 stf (stf (stf (error "too deep"))) 3 == 6 "fix" just does that as many times as necessary, so we can define factorial = fix step_towards_factorial The connection between the "half function" approach and the fix operator is this: we want fix f = (f (fix f)), which is a recursive definition, so we can use the "half function" technique to make it: half_fix me f = f (me me f) fix = half_fix half_fix -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Vincent Kraeutler wrote:
Donald Bruce Stewart wrote:
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
this is cute indeed! (do you keep an emergency reserve of those around for situations like this? ;-))
LOL! I bet he does as well... I don't know. I try to tell people Haskell can be beautifully readable and concise. But there is no denying that Haskell can *also* be cryptic beyond belief! Even *I* am unable to figure out how the hell that works. Heck I only even know what it *does* because I got the computer to execute it for me... o_O

Vincent Kraeutler wrote:
Donald Bruce Stewart wrote:
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
either way, if one of the Masters Of The Shadow Y Style on this list feels like throwing in another koan or two, you'll have at least one thankful audience member ;-)
Rewriting in a more beginner form: s = 1 : scanl (+) 1 s Recursively defined lists are sometimes hard to predict. Here is a systematic way of watching what it does. Inspired by a theorem about fixed points, the following sequence gets closer and closer to the solution to s = f s: _|_, f _|_, f (f _|_), f (f (f _|_)), ... Applying this to our example, _|_ 1 : scanl (+) 1 _|_ = 1:1:_|_ 1 : scanl (+) 1 (1:1:_|_) = 1:1:2:3:_|_ 1 : scanl (+) 1 (1:1:2:3:_|_) = 1:1:2:3:5:8:_|_ You can continue the process until you run out of patience or you see the pattern. It is an alternative way to execute the recursion. It is harder in some cases (e.g., recursive functions) but easier in some others (e.g., recursive lists). Executing a program to look for a pattern is the hardest way to understand it. (Sadly, in most schools it is the only way taught.) Deriving it from a specification provides more insight, answers the itching question "so how did you come up with this magic", takes away the mysticism, teaches more lessons, and moves programming closer to science-based engineering and further from secret-based guild. We wish to compute a fibonacci-like sequence s with given s0 and s1, and s(n+2) = s(n+1) + sn afterwards. We already know a million ways, but today we add one more. After some exploration, we find s(n+1) = s1 + (s0 + s1 + s2 + ... + s(n-1)) = scanl (+) s1 s !! n (This applies to s1 too: scanl (+) s1 s !! 0 = s1.) Let me abbreviate "scanl (+) s1 s" as "f s". So s(n+1) = f s !! n. s = [s0, s1, s2, s3, ...] = [s0, f s !! 0, f s !! 1, f s !! 2, ...] = s0 : f s = s0 : scanl (+) s1 s Now we have it.

On 5/28/07, Donald Bruce Stewart
This thread should end, guys. It is inappropriate for the Haskell lists, and appears to have been a simple misunderstanding anyway.
Thanks everyone. Please stay friendly!
-- Don
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
Speaking of cute code, I'm fond of this: map length . List.group . Control.Monad.Fix.fix $ show And other (longer) variations which generate only powers of two. It's a great conversation starter for teaching about fix. Jason

i would just like to say thank you for all the extensive replies. after fiddling with them for an afternoon i'm positive i grokked the concept. it's just too bad the nice wrapper concept from [1] does not seem to be directly applicable to fix in haskell, since they require untyped side-effects.... anyhow, this has been very instructive. thanks again! v. [1] http://citeseer.ist.psu.edu/mcadams01practical.html Jason Dagit wrote:
On 5/28/07, Donald Bruce Stewart
wrote: This thread should end, guys. It is inappropriate for the Haskell lists, and appears to have been a simple misunderstanding anyway.
Thanks everyone. Please stay friendly!
-- Don
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
Speaking of cute code, I'm fond of this:
map length . List.group . Control.Monad.Fix.fix $ show
And other (longer) variations which generate only powers of two. It's a great conversation starter for teaching about fix.
Jason _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Jason Dagit wrote:
On 5/28/07, Donald Bruce Stewart
wrote: P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
Speaking of cute code, I'm fond of this:
map length . List.group . Control.Monad.Fix.fix $ show
Indeed, very nice examples! I actually misread the first one as Control.Monad.Fix.fix ((1:) . tail . scanl (+) 1) which is quite nice too, although map (2^) [0..] would be much simpler! ;-) Zun.

Roberto Zunino wrote:
I actually misread the first one as
Control.Monad.Fix.fix ((1:) . tail . scanl (+) 1)
which is quite nice too, although
map (2^) [0..]
would be much simpler! ;-)
We apply a lesson learned from my last derivation. The lesson was to look at s!!(n+1). s = 1 : tail (scanl (+) 1 s) s!!(n+1) = (1 : tail (scanl (+) 1 s))!!(n+1) = tail (scanl (+) 1 s) !! n = scanl (+) 1 s !! (n+1) = 1 + s!!0 + s!!1 + s!!2 + ... + s!!n It turns out that we can generalize it a bit to s!!n = 1 + s!!0 + ... + s!!(n-1) since, in case n=0, it gives s!!0 = 1 + empty sum, which is still right. But now plugging the equation of s!!n into that of s!!(n+1) gives s!!(n+1) = 1 + s!!0 + s!!1 + s!!2 + ... s!!(n-1) + s!!n = s!!n + s!!n = 2 * s!!n Together with s!!0 = 1, this explains why s!!n = 2^n.

On 5/29/07, PR Stanley
Yet, you seem to be desperate to keep the thread alive.
As long as I'm personally attacked. But whatever, let's forget about it, you already said it's been a bad day. End of flamebait
participants (13)
-
Albert Y. C. Lai
-
Alfonso Acosta
-
Andrew Coppin
-
Bayley, Alistair
-
David House
-
dons@cse.unsw.edu.au
-
Jason Dagit
-
Jon Fairbairn
-
kahl@cas.mcmaster.ca
-
PR Stanley
-
Roberto Zunino
-
Tomasz Zielonka
-
Vincent Kraeutler