RE: [Haskell-cafe] Project postmortem

2005-11-18 Thread Simon Peyton-Jones
| Unless lightning strikes and tomorrow morning I figure out what's the | deal with the spurious Mac OSX crashes, I think this might be my last | network app in Haskell. I should really be spending time on the | business end of the app intead of figuring out platform differences | and the like.

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Joel Reymont
On Nov 18, 2005, at 10:17 AM, Simon Peyton-Jones wrote: I hope you don't abandon Haskell altogether. Without steady, friendly pressure from applications-end folk like you, things won't improve. Nah, I'm just having a very frustrating Friday. I think I need some direction in which to dig

The IT buzzword of the next decade (was Re: [Haskell-cafe] Project postmortem)

2005-11-18 Thread Joel Reymont
This would be a good new thread to discuss it ;-) On Nov 18, 2005, at 10:42 AM, Jan Stoklasa (gmail) wrote: Hi, so sad, so true... At least haskell ideas sneak into mainstream languages under disguise (LINQ anyone?). C-Java-C# syntax that business developers and their bosses love so much

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Glynn Clements
Sebastian Sylvan wrote: How about (¤)? It looks like a ring to me, I'm not sure where that's located on a EN keyboard, but it's not terribly inconvenient on my SE keyboard. f ¤ g looks better than f . g for function composition, if you ask me. That symbol actually does look

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Sebastian Sylvan
On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote: On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote: Some people do use it more often than I do, but I find that in most cases except simple pipelined functions it only makes the code harder to read. But this case is

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread John Meacham
I always fancied () as a synonym for 'mappend' John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Records

2005-11-18 Thread Ketil Malde
Fraser Wilson [EMAIL PROTECTED] writes: Isn't there a potential for confusion with function composition (f . g)? Perhaps, but I always have spaces on either side when it's function composition. Good for you. Syntax that changes depending on spacing is my number one

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Tomasz Zielonka
On Fri, Nov 18, 2005 at 12:21:09PM +0100, Sebastian Sylvan wrote: On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote: On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote: Some people do use it more often than I do, but I find that in most cases except simple pipelined

RE: [Haskell-cafe] Project postmortem

2005-11-18 Thread Simon Marlow
On 18 November 2005 10:48, Joel Reymont wrote: On Nov 18, 2005, at 10:17 AM, Simon Peyton-Jones wrote: I hope you don't abandon Haskell altogether. Without steady, friendly pressure from applications-end folk like you, things won't improve. Nah, I'm just having a very frustrating

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Joel Reymont
On Nov 18, 2005, at 1:55 PM, Simon Marlow wrote: You can get debugging output by compiling your program with -debug, and then running it with some of the -Dsomething options (use +RTS -? for a list, +RTS -Ds is a good one to start with). I'm still working on a repro case but here's what I

RE: [Haskell-cafe] Project postmortem

2005-11-18 Thread Simon Marlow
On 18 November 2005 14:42, Joel Reymont wrote: On Nov 18, 2005, at 1:55 PM, Simon Marlow wrote: You can get debugging output by compiling your program with -debug, and then running it with some of the -Dsomething options (use +RTS -? for a list, +RTS -Ds is a good one to start with). I'm

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Sebastian Sylvan
On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote: On Fri, Nov 18, 2005 at 12:21:09PM +0100, Sebastian Sylvan wrote: On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote: On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote: Some people do use it more often than I do,

Re: [Haskell-cafe] How to use a wiki to annotate GHC Docs? was Re: [Haskell] Re: Making Haskell more open

2005-11-18 Thread Cale Gibbard
On 18/11/05, Wolfgang Jeltsch [EMAIL PROTECTED] wrote: Am Mittwoch, 16. November 2005 20:02 schrieb Cale Gibbard: [...] It's unfortunate, but if you don't put a little bit of effort into defending your forms, they will eventually get quite a lot of spam. Cleaning up 600+ pages by hand

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Jason Dagit
On Nov 18, 2005, at 2:17 AM, Simon Peyton-Jones wrote: I hope you don't abandon Haskell altogether. Without steady, friendly pressure from applications-end folk like you, things won't improve. It's incredibly valuable feedback. But I can see that when you have to deliver something next

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Paul Hudak
This is a very late response to an old thread... Tom Hawkins wrote: In a pure language, is it possible to detect cycles in recursive data structures? For example, is it possible to determine that cyclic has a loop? ... data Expr = Constant Int | Addition Expr Expr cyclic :: Expr cyclic

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Henning Thielemann
On Fri, 18 Nov 2005, Paul Hudak wrote: For example: fe1,fe2 :: Fix Expr fe1 e = Add (Const 1) (Const 1) -- non-recursive fe2 e = Add (Const 1) e -- recursive Do you mean fe1 _ = Add (Const 1) Loop ? ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Cale Gibbard
test.wagerlabs.com seems really slow for me right now. I've mirrored the repo on my own machine (might not be 100% reliable, but should stay up nearly all of the time). The mirror address is http://vx.hn.org/postmortem/ - Cale On 18/11/05, Joel Reymont [EMAIL PROTECTED] wrote: Folks, This is

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Sven Panne
Am Freitag, 18. November 2005 17:16 schrieb Jason Dagit: [...] I was playing with one of the Haskell OpenGL libraries (actually it's a refined FFI) over the summer and some things about it rubbed me the wrong way. I wanted to try fixing them but I really couldn't figure out how to get ahold

[Haskell-cafe] Function application like a Unix pipe

2005-11-18 Thread Scherrer, Chad
I'm still trying to settle on a feel for good programming style in Haskell. One thing I've been making some use of lately is (\|) = flip ($) infixl 0 \| Then expressions like f4 $ f3 $ f2 $ f1 $ x become x \| f1 \| f2 \| f3 \| f4 I've seen something like this on haWiki using (#), but I

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Greg Woodhouse
--- Paul Hudak [EMAIL PROTECTED] wrote: This is a very late response to an old thread... Tom Hawkins wrote: In a pure language, is it possible to detect cycles in recursive data structures? For example, is it possible to determine that cyclic has a loop? ... data Expr =

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Joel Reymont
The exception is actually from withTimeOut. Removing calls to that lets the handshake proceed. The server is using a client handshake, though, so the handshake of client vs. client goes on indefinitely. I'm fixing the server side and once that is done will clean up SSL at the end of the

[Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Greg Woodhouse
Maybe this is old hat, but the question about detecting loops in data structures got me thinking about this. I know you can encode the cons operator (and ordinary lists) in pure lambda calculus, but how could you possibly represent something like [0, 1..]? One thought that occurss to me is to

Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Lennart Augustsson
What do you mean by represent? It's easy enough to write down the lambda term that is the encoding of [0..]. -- Lennart Greg Woodhouse wrote: Maybe this is old hat, but the question about detecting loops in data structures got me thinking about this. I know you can encode the cons

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Paul Hudak
Henning Thielemann wrote: On Fri, 18 Nov 2005, Paul Hudak wrote: For example: fe1,fe2 :: Fix Expr fe1 e = Add (Const 1) (Const 1) -- non-recursive fe2 e = Add (Const 1) e -- recursive Do you mean fe1 _ = Add (Const 1) Loop ? No, I really meant it as written. I included this

Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Greg Woodhouse
--- Lennart Augustsson [EMAIL PROTECTED] wrote: What do you mean by represent? It's easy enough to write down the lambda term that is the encoding of [0..]. -- Lennart You mean like \x - x ? If I apply it to the Church numeral i, I get i in return. But that hardly seems

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Paul Hudak
Greg Woodhouse wrote: --- Paul Hudak [EMAIL PROTECTED] wrote: Tom Hawkins wrote: In a pure language, is it possible to detect cycles in recursive data structures? For example, is it possible to determine that cyclic has a loop? ... data Expr = Constant Int | Addition Expr Expr

Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Lennart Augustsson
How about: nil = \ n c . n cons x xs = \ n c . c x xs zero = \ z s . z suc n = \ z s . s n listFromZero = Y ( \ from n . cons n (from (suc n))) zero (Untested, so I might have some mistake.) -- Lennart Greg Woodhouse wrote: --- Lennart Augustsson [EMAIL PROTECTED] wrote: What

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Greg Woodhouse
--- Paul Hudak [EMAIL PROTECTED] wrote: I suspect from your other post that you haven't seen the standard trick of encoding infinite data structures as fixpoints. Suppose you have a lambda calculus term for cons, as well as for the numeral 1. Then the infinite list of ones is just:

Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Greg Woodhouse
--- Lennart Augustsson [EMAIL PROTECTED] wrote: How about: nil = \ n c . n cons x xs = \ n c . c x xs zero = \ z s . z suc n = \ z s . s n listFromZero = Y ( \ from n . cons n (from (suc n))) zero (Untested, so I might have some mistake.) -- Lennart Okay, I see what

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Paul Hudak
Greg Woodhouse wrote: --- Paul Hudak [EMAIL PROTECTED] wrote: Y (\ones. cons 1 ones) where Y (aka the paradoxical combinator or fixed point combinator) is defined as: \f. (\x. f (x x)) (\x. f (x x)) Now, this is I have seen, but it frankly strikes me as a formal trick. I've never felt that

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Benjamin Franksen
On Friday 18 November 2005 02:59, you wrote: On Nov 17, 2005, at 1:52 PM, Benjamin Franksen wrote: ... Yes, yes, yes. I'd rather use a different operator for record selection. For instance the colon (:). Yes, I know it is the 'cons' operator for a certain concrete data type that

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Greg Woodhouse
--- Paul Hudak [EMAIL PROTECTED] wrote: The important property of Y is this: Y f = f (Y f) Right. This is just a formal statement of the property thaat f fixex Y f. I'm with you so far. In this way you can see it as unwinding the function, one step at a time. If we define f as

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Lennart Augustsson
Greg Woodhouse wrote: --- Paul Hudak [EMAIL PROTECTED] wrote: The important property of Y is this: Y f = f (Y f) Right. This is just a formal statement of the property thaat f fixex Y f. I'm with you so far. In this way you can see it as unwinding the function, one step at a time. If

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread John Meacham
On Fri, Nov 18, 2005 at 04:22:59PM +0100, Sebastian Sylvan wrote: Yes. I just don't think it's used enough to warrant giving it one of the best symbols. grep -o ' [-+.*/[EMAIL PROTECTED] ' GenUtil.hs | sort | uniq -c | sort -n 1 $! 1 * 8 + 10 == 12 -

Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Lennart Augustsson
Greg Woodhouse wrote: --- Lennart Augustsson [EMAIL PROTECTED] wrote: How about: nil = \ n c . n cons x xs = \ n c . c x xs zero = \ z s . z suc n = \ z s . s n listFromZero = Y ( \ from n . cons n (from (suc n))) zero (Untested, so I might have some mistake.) -- Lennart

Re: [Haskell-cafe] Infinite lists and lambda calculus

2005-11-18 Thread Lennart Augustsson
Greg Woodhouse wrote: Perhaps the issue is that the manipulations below are purely syntactic, But all the computation rules of the lambda calculus are syntactic in that sense. When you can prove things by symbol pushing it's the easiest way. But as Paul Hudak mentioned, there definitions that

Re: [Haskell-cafe] Formalizing lazy lists?

2005-11-18 Thread Greg Woodhouse
--- Lennart Augustsson [EMAIL PROTECTED] wrote: Unfolding Y is indeed part of the algorithm to generate the list. The lambda calculus is just another programming language, so why does this disturb you? Well...think about this way. The function f i = [1, 1 ..]!!i is just a constant

Re: [Haskell-cafe] Infinite lists and lambda calculus

2005-11-18 Thread Greg Woodhouse
--- Lennart Augustsson [EMAIL PROTECTED] wrote: It computes the fix point which you can also define as oo fix f = lub f^i(_|_) i=0 where f^i is f iterated i times. Is that a definition of fixpoint that makes you happier? Believe it or not, yes.

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread jerzy . karczmarczuk
My simple-mindness and naïveté begin to bother me. I begin to get lost, and I don't know anymore what is the problem... Greg Woodhouse a eacute;crit: --- Paul Hudak [EMAIL PROTECTED] wrote: ... The important property of Y is this: Y f = f (Y f) Right. This is just a formal statement of

Re: [Haskell-cafe] Project postmortem

2005-11-18 Thread Joel Reymont
I'm happy to report that the problem can be reproduced by running the code from my darcs repo at http://test.wagerlabs.com/postmortem. See the README file. I'm on Mac OSX 10.4.3. The server just sits there, goes through the SSL handshake and... does nothing else. The clients go through the

Re: [Haskell-cafe] Infinite lists and lambda calculus (was: Detecting Cycles in Datastructures)

2005-11-18 Thread Cale Gibbard
On 18/11/05, Greg Woodhouse [EMAIL PROTECTED] wrote: --- Lennart Augustsson [EMAIL PROTECTED] wrote: I guess I'm not doing a very good job of expressing myself. I see that if you define Y as you do, then the various functions you list have the property that Y f = f (Y f). I don't want to

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-18 Thread Benjamin Franksen
On Saturday 19 November 2005 02:16, Greg Woodhouse wrote: --- [EMAIL PROTECTED] wrote: fix f = f (fix f) -- Here you have your Y. No typeless lambda. g f n = n : f n-- This is a generic *non-recursive* `repeat` ones = fix g 1 -- Guess what. Very nice! I honestly would not have

Re: [Haskell-cafe] Infinite lists and lambda calculus

2005-11-18 Thread Paul Hudak
Cale Gibbard wrote: Y = (\f. (\x. f (x x)) (\x. f (x x))) In a sense, the real definition of Y is Y f = f (Y f), this lambda term just happens to have that property, but such functions aren't rare. Actually no, the real definition is the top one, because the other one isn't even a valid

Re: [Haskell-cafe] Infinite lists and lambda calculus

2005-11-18 Thread Cale Gibbard
On 18/11/05, Paul Hudak [EMAIL PROTECTED] wrote: Cale Gibbard wrote: Y = (\f. (\x. f (x x)) (\x. f (x x))) In a sense, the real definition of Y is Y f = f (Y f), this lambda term just happens to have that property, but such functions aren't rare. Actually no, the real definition is the