Re: Re[2]: [Haskell-cafe] FFI basics

2007-02-12 Thread Yitzchak Gale
Bulat Ziganshin wrote: examples of lifting C functions into Haskell world: mysin :: Double - Double mysin = realToFrac . c_mysin . realToFrac -- c_mysin :: CDouble - CDouble rnd :: Int - IO Int rnd x = do r - c_rnd (fromIntegral x) return (fromIntegral r) -- c_rnd :: CInt - IO

Re: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Lennart Augustsson
Many architectures gives both the quotient and remainder when you use the division instruction, so divMod (quotRem) shouldn't cost more than a div or mod. But if the code generator takes advantage of that is another matter. On Feb 12, 2007, at 02:32 , Matthew Brecknell wrote: I wrote:

[Haskell-cafe] Re: Optimization fun

2007-02-12 Thread DavidA
Lennart Augustsson lennart at augustsson.net writes: Yes, and that's pretty much what my version does (and what the original tried to do?). Yes, you're right, I see now that my method is equivalent to yours. (My apologies, it was late.) The point I was trying to make is that there are two

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Joel Reymont
On Feb 12, 2007, at 5:45 AM, Matt Roberts wrote: - The hackathon videos, - A transformation-based optimiser for Haskell, - An External Representation for the GHC Core Language (DRAFT for GHC5.02), and - Secrets of the Glasgow Haskell Compiler inliner. Matt, can you please post

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Joel Reymont
On Feb 12, 2007, at 7:06 AM, Stefan O'Rear wrote: We have Core because Simon lacks the patience to solve the halting problem and properly perform effects analysis on STG. We have STG because Simon lacks the patience to wait for the 6.6 Simplifier to finish naively graph-reducing every

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Pixel
Chris Moline [EMAIL PROTECTED] writes: dropWhile p = foldr (\x l' - if p x then l' else x:l') [] invalid: dropWhile ( 5) [1, 10, 1] should return [10, 1] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Donald Bruce Stewart
pixel: Chris Moline [EMAIL PROTECTED] writes: dropWhile p = foldr (\x l' - if p x then l' else x:l') [] invalid: dropWhile ( 5) [1, 10, 1] should return [10, 1] Prelude Test.QuickCheck Text.Show.Functions quickCheck $ \p xs - dropWhile p xs == foldr (\x l' - if p x then l' else x:l')

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Dougal Stanton
Quoth Joel Reymont, nevermore, Are these two different Simons? :-) I'm beginning to wonder if Simon is less a name and more a title, meaning strong in the lambda force or somesuch. Let's hope they don't go over to the dark side ;-) -- Dougal Stanton

Re: [Haskell-cafe] Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-12 Thread Yitzchak Gale
[EMAIL PROTECTED] wrote: Still, in the interest of purity, here it is, in Haskell. As the original Eratosthenes sieve, this algorithm uses only successor and predecessor operations. I don't think the Greeks had too much trouble with addition. If that is the case, then Rafael's definition is

Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Yitzchak Gale
Lennart Augustsson wrote: I'm not sure what you're asking. The (untyped) lambda calculus is Turing complete. How could seq improve that? Obviously, it can't. But how can it hurt? Classical lambda calculus does not model the semantics of laziness, so seq is equivalent to flip const there,

[Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread Eric Willigers
Eric Willigers wrote: Do the two programs implement the same algorithm? The C program updates x and y in sequence. The Haskell program updates x and y in parallel and can be easier for the compiler to optimize. Hi Don, Expressing this in other words, do we want the new y to be based on the

Re[2]: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Bulat Ziganshin
Hello Lennart, Monday, February 12, 2007, 11:53:32 AM, you wrote: Many architectures gives both the quotient and remainder when you use the division instruction, so divMod (quotRem) shouldn't cost more than a div or mod. But if the code generator takes advantage of that is another matter.

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Bulat Ziganshin
Hello Matt, Monday, February 12, 2007, 8:45:47 AM, you wrote: I am trying to get a deeper understanding of core's role in GHC and i'm not sure but may be these papers that say about STG can help you: Implementing lazy functional languages on stock hardware: the Spineless Tagless G-machine.

Re[2]: [Haskell-cafe] questions about core

2007-02-12 Thread Bulat Ziganshin
Hello Joel, Monday, February 12, 2007, 12:23:16 PM, you wrote: - Secrets of the Glasgow Haskell Compiler inliner. Matt, can you please post pointers to the above? mostly, these are available on papers pages of SM and SPJ: http://research.microsoft.com/~simonpj/

Re: [Haskell-cafe] FFI basics

2007-02-12 Thread Sven Panne
On Monday 12 February 2007 09:54, Yitzchak Gale wrote: Bulat Ziganshin wrote: examples of lifting C functions into Haskell world: mysin :: Double - Double mysin = realToFrac . c_mysin . realToFrac -- c_mysin :: CDouble - CDouble rnd :: Int - IO Int rnd x = do r - c_rnd

[Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Gracjan Polak
Hi, I wanted to setup really simple http server, found Network.CGI.Compat.pwrapper and decided it suits my needs. Code: module Main where import Network.CGI import Text.XHtml import Network doit vars = do return (body (toHtml (show vars))) main = withSocketsDo (pwrapper (PortNumber )

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Nicolas Frisby
Guess this is a tricky choice for a foldr intro, since it requires a paramorphism (see bananas lenses wires etc.) para :: (a - [a] - b - b) - b - [a] - b para f e [] = e para f e (x:xs) = f x xs (para f e xs) -- note that the original tail of the list (i.e. xs and not xs') is used in the

[Haskell-cafe] pythags

2007-02-12 Thread phiroc
Hello, the Advanced Monads page in the Haskell Wikibook (http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the following example of a List Monad pythags = do x - [1..] y - [x..] z - [y..] guard (x^2 + y^2 == z^2) return (x, y, z) However,

Re: [Haskell-cafe] pythags

2007-02-12 Thread Greg Fitzgerald
Check out Hoogle: http://haskell.org/hoogle/?q=guard import Control.Monad -Greg On 2/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Hello, the Advanced Monads page in the Haskell Wikibook (http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the following example of a List

Re: [Haskell-cafe] pythags

2007-02-12 Thread Robert Dockins
On Feb 12, 2007, at 11:02 AM, [EMAIL PROTECTED] wrote: Hello, the Advanced Monads page in the Haskell Wikibook (http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the following example of a List Monad pythags = do x - [1..] y - [x..] z - [y..]

Re: [Haskell-cafe] pythags

2007-02-12 Thread Creighton Hogg
On 2/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Hello, the Advanced Monads page in the Haskell Wikibook (http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the following example of a List Monad pythags = do x - [1..] y - [x..] z - [y..] guard

Re: [Haskell-cafe] pythags

2007-02-12 Thread Robert Dockins
On Feb 12, 2007, at 11:02 AM, [EMAIL PROTECTED] wrote: Hello, the Advanced Monads page in the Haskell Wikibook (http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the following example of a List Monad pythags = do x - [1..] y - [x..] z - [y..]

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Kirsten Chevalier
On 2/11/07, Matt Roberts [EMAIL PROTECTED] wrote: - Exactly what are the operational and denotational semantics of core? Since I don't think this question has been answered yet, here's a mailing list post from Simon PJ that probably answers it:

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Kirsten Chevalier
On 2/12/07, Dougal Stanton [EMAIL PROTECTED] wrote: Quoth Joel Reymont, nevermore, Are these two different Simons? :-) I'm beginning to wonder if Simon is less a name and more a title, meaning strong in the lambda force or somesuch. Let's hope they don't go over to the dark side ;-) I

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Bernie Pope
Nicolas Frisby wrote: Guess this is a tricky choice for a foldr intro, since it requires a paramorphism (see bananas lenses wires etc.) para :: (a - [a] - b - b) - b - [a] - b para f e [] = e para f e (x:xs) = f x xs (para f e xs) -- note that the original tail of the list (i.e. xs and not

Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Lennart Augustsson
Adding seq ruins eta reduction. For normal order lambda calculus we have '\x.f x = f' (x not free in f). If we add seq this is no longer true. I'm not sure why you bring up lazy evaluation (I presume you mean lazy evaluation as in call-by-need). Having call-by-need or not is unobservable,

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Nicolas Frisby
Oops; I totally forgot the context of this whole discussion! I enjoyed your article. On 2/12/07, Bernie Pope [EMAIL PROTECTED] wrote: Nicolas Frisby wrote: Guess this is a tricky choice for a foldr intro, since it requires a paramorphism (see bananas lenses wires etc.) para :: (a - [a] - b

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Lennart Augustsson
Sure, but we also have para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs So I think using para is fine. -- Lennart On Feb 12, 2007, at 18:40 , Bernie Pope wrote: Nicolas Frisby wrote: Guess this is a tricky choice for a foldr intro, since it requires a

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Robert Dockins
On Feb 12, 2007, at 1:31 PM, Kirsten Chevalier wrote: On 2/11/07, Matt Roberts [EMAIL PROTECTED] wrote: - Exactly what are the operational and denotational semantics of core? Since I don't think this question has been answered yet, here's a mailing list post from Simon PJ that probably

Re: [Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Bjorn Bringert
On Feb 12, 2007, at 14:22 , Gracjan Polak wrote: I wanted to setup really simple http server, found Network.CGI.Compat.pwrapper and decided it suits my needs. Code: module Main where import Network.CGI import Text.XHtml import Network doit vars = do return (body (toHtml (show vars)))

Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Bernie Pope
Lennart Augustsson wrote: Sure, but we also have para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs Nice one. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread Donald Bruce Stewart
ewilligers: Eric Willigers wrote: Do the two programs implement the same algorithm? The C program updates x and y in sequence. The Haskell program updates x and y in parallel and can be easier for the compiler to optimize. Hi Don, Expressing this in other words, do we want the new y

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Kirsten Chevalier
On 2/12/07, Robert Dockins [EMAIL PROTECTED] wrote: At the risk of sounding self-promoting, I'd like to point out that the research paper I recently announced defines an intermediate language that is similar to GHC's core in some respects (they are both based on System F_omega). I give a full

Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread David Roundy
On Tue, Feb 13, 2007 at 08:18:25AM +1100, Donald Bruce Stewart wrote: Now, if we rewrite it to not use the temporary: go :: Double - Double - Int - IO () go !x !y !i | i == 10 = printf %.6f\n (x+y) | otherwise = go (x*y/3) (x*9) (i+1) for (;

Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Claus Reinke
Adding seq ruins eta reduction. For normal order lambda calculus we have '\x.f x = f' (x not free in f). If we add seq this is no longer true. isn't that a problem of seq (and evaluation in Haskell generally) not being strict enough (ie, forcing evaluation only to weak head normal form

Re: [Haskell-cafe] questions about core

2007-02-12 Thread Matt Roberts
On 12/02/2007, at 8:23 PM, Joel Reymont wrote: On Feb 12, 2007, at 5:45 AM, Matt Roberts wrote: - The hackathon videos, @electronic{hack06, Author = {Simon Peyton Jones and Malcolm Wallace and et. al.}, Date-Added = {2007-02-13 09:04:47 +1100}, Date-Modified =

[Haskell-cafe] Re: Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread apfelmus
Bernie Pope wrote: Lennart Augustsson wrote: Sure, but we also have para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs Nice one. Nice one is an euphemism, it's exactly solution one :) Regards, apfelmus ___ Haskell-Cafe mailing

[Haskell-cafe] Re: Parsec and Java

2007-02-12 Thread Benjamin Franksen
Arnaud Bailly wrote: Joel Reymont wrote: Is there a Java parser implemented using Parsec? There is: http://jparsec.codehaus.org/ Jparsec is an implementation of Haskell Parsec on the Java platform. I think Joel was asking for a parser for the Java language, written in Haskell using the

Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread Bryan O'Sullivan
David Roundy wrote: I'm rather curious (if you're sill interested) how this'll be affected by the removal of the division from the inner loop. e.g. go :: Double - Double - Int - IO () go !x !y !i | i == 10 = printf %.6f\n (x+y) | otherwise = go

Re: [Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Albert Y. C. Lai
Bjorn Bringert wrote: pwrapper is not an HTTP server, though the Haddock comment can make you think so. pwrapper allows you to talk *CGI* over a TCP port, but I have no idea why anyone would like to do that. Here is a scenerio. I want a basic web application: someone makes a request, and my

Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread David Roundy
On Mon, Feb 12, 2007 at 02:25:21PM -0800, Bryan O'Sullivan wrote: David Roundy wrote: I'm rather curious (if you're sill interested) how this'll be affected by the removal of the division from the inner loop. e.g. go :: Double - Double - Int - IO () go !x !y !i | i ==

Re: [Haskell-cafe] Re: Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Lennart Augustsson
I thought solution one was missing the ~ ? On Feb 12, 2007, at 22:07 , [EMAIL PROTECTED] wrote: Bernie Pope wrote: Lennart Augustsson wrote: Sure, but we also have para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs Nice one. Nice one is an euphemism, it's exactly

[Haskell-cafe] Summer of Code

2007-02-12 Thread Bryan Burgers
Hello, Yes, I realize it's mid-February right now and the summer is still months away, but it's probably not too early to think about the future. I am wondering if there are any Summer of Code projects that I would be able to do for the Haskell community. I will be graduating from my undergrad

Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Lennart Augustsson
No, I can't say off hand if seq-hnf would keep eta valid, either. Neither do I know how to implement seq-hnf efficiently. :) As far as eta for other types, yes, I'll take it if I can get it's easily. But I'm also pretty happy with encoding all the other data types within the lambda calculus

Re: [Haskell-cafe] Summer of Code

2007-02-12 Thread Donald Bruce Stewart
bryan.burgers: Hello, Yes, I realize it's mid-February right now and the summer is still months away, but it's probably not too early to think about the future. I am wondering if there are any Summer of Code projects that I would be able to do for the Haskell community. I will be

[Haskell-cafe] Even better Eratosthenes sieve and lucky numbers

2007-02-12 Thread oleg
We further simplify the previously posted genuine sieve algorithm and generalize it to the finding of lucky numbers. We observe that we only need to store marks _signifying_ the integers, but never the integers themselves. Thus we arrive at the algorithm that is distinguished from all

[Haskell-cafe] ANNOUNCE: urlcheck 0.1, (smp) parallel link checker

2007-02-12 Thread Donald Bruce Stewart
This little tool has been kicking around on my harddrive for a month or two now, so time to release! I'm pleased to announce the first release of urlcheck, an parallel link checker, written in Haskell. Frustrated with the resources and time consumed by 'linkchecker', when preparing the weekly

Re: Re[2]: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Matthew Brecknell
Lennart Augustsson said: Many architectures gives both the quotient and remainder when you use the division instruction, so divMod (quotRem) shouldn't cost more than a div or mod. But if the code generator takes advantage of that is another matter. You're quite right. Bulat Ziganshin