[Haskell-cafe] Re: Chameneos

2006-01-07 Thread Aaron Denney
On 2006-01-06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote: > One could make an MVar version which did not use a meeting thread, and I > welcome someone to do that. I have no proof that the current solution > is really the fastest architecture. I've done so -- on my machine it's comparable (within

Re: Re[2]: [Haskell-cafe] Expanding do notation

2006-01-07 Thread David F . Place
Thanks Bulat and Chris for helping me to understand this. I just found a perfect description in Rabhi and Lapalme's book _Algorithms: a Functional Programming Approach_ , Chapter 3 "The efficiency of functional programs. On Jan 7, 2006, at 5:56 PM, Bulat Ziganshin wrote: Hello David, Sa

Re: [Haskell-cafe] fastest Binary library!

2006-01-07 Thread Donald Bruce Stewart
bulatz: > Hello > > yes, i did it! today i spend time to optimize my own Binary library > and got the (de)serialization speed about 50 mb/s with my 1 ghz cpu. > it is a peek speed for unboxed arrays, in real life GC times and other > overhead expenses will need much more time than (de)serializatio

[Haskell-cafe] do {x<-[1,2,3]; True <- return (odd x); return x}.. why? (do notation, monads, guards)

2006-01-07 Thread Marc Weber
Here is a simple program implementing the above function in 4 different ways.. See my comments to get to know where I have problems: -- begin test.hs -- module Main where import IO import Control.Monad.List {- list1,2 are both implementations of the same function f=[1,3] ;-)

Re[2]: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Bulat Ziganshin
Hello David, Saturday, January 07, 2006, 8:37:01 PM, you wrote: >> the mind-bending-thing I had to learn with Haskell is that the "let p =" >> creates source code *shorthand*. DFP> Yes, this is just what I need to understand. Could you point me to a DFP> description of this? I couldn't find any

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread David F. Place
On Jan 7, 2006, at 2:23 PM, Chris Kuklewicz wrote: The mantra is : Bindings are not variables The best, official thing to read is section 3.12 of the Haskell98 Report: http://www.haskell.org/onlinereport/exps.html#sect3.12 Yes, I had already looked there, but didn't achieve enlightenment

[Haskell-cafe] fastest Binary library!

2006-01-07 Thread Bulat Ziganshin
Hello yes, i did it! today i spend time to optimize my own Binary library and got the (de)serialization speed about 50 mb/s with my 1 ghz cpu. it is a peek speed for unboxed arrays, in real life GC times and other overhead expenses will need much more time than (de)serialization itself. but at lea

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Chris Kuklewicz
Mmmm...now I had to go look it up. David F. Place wrote: > Hi Chris, > > Yes, this is just what I need to understand. Could you point me to a > description of this? I couldn't find any discussion of it in the > reference document. Thanks. > > Cheers, David > > On Jan 7, 2006, at 12:25 PM,

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread David F. Place
Hi Chris, Yes, this is just what I need to understand. Could you point me to a description of this? I couldn't find any discussion of it in the reference document. Thanks. Cheers, David On Jan 7, 2006, at 12:25 PM, Chris Kuklewicz wrote: the mind-bending-thing I had to learn with Haske

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Chris Kuklewicz
Ooops, > headOfP <- return (Control.Excection.evaluate (head p)) should be > headOfP <- (Control.Excection.evaluate (head p)) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Chris Kuklewicz
Josef Svenningsson wrote: > > > On 1/7/06, *Chris Kuklewicz* <[EMAIL PROTECTED] > > wrote: > > When you put "print (head p)" at then end, it keeps a reference to the > whole list "p" which is your space leak. If you want to store the head > of p, this *shou

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Chris Kuklewicz
David F. Place wrote: > > On Jan 7, 2006, at 11:56 AM, Chris Kuklewicz wrote: > >> This is all about lazy evaluation. Ah. Sorry then. > > > Actually, I understand about lazy evaluation. What I don't understand > is the extent of variable bindings. The binding has a lexical extent. The "

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Josef Svenningsson
On 1/7/06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote: When you put "print (head p)" at then end, it keeps a reference to thewhole list "p" which is your space leak.  If you want to store the headof p, this *should* work:> main = do n <- getArgs >>= return . read . head >   let p = permutati

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread David F. Place
On Jan 7, 2006, at 11:56 AM, Chris Kuklewicz wrote: This is all about lazy evaluation. Actually, I understand about lazy evaluation. What I don't understand is the extent of variable bindings. If I desugar the code this far: main = do n <- getArgs >>= return . read . head

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Chris Kuklewicz
David F. Place wrote: > Hi All, > > Is there a program for expanding 'do' notation? I am trying to > understand why the following code (from the Fannkuch entry) doesn't > hold onto the list 'p' causing a space leak. You mean "doesn't hold onto the list 'p' preventing a space leak.

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Robin Green
David F. Place wrote: Hi All, Is there a program for expanding 'do' notation? I am trying to understand why the following code (from the Fannkuch entry) doesn't hold onto the list 'p' causing a space leak. You can desugar (i.e. expand) the do notation relatively easily, but that won't te

[Haskell-cafe] Expanding do notation

2006-01-07 Thread David F. Place
Hi All, Is there a program for expanding 'do' notation? I am trying to understand why the following code (from the Fannkuch entry) doesn't hold onto the list 'p' causing a space leak. main = do n <- getArgs >>= return . read . head let p = permutations [1..n] mapM_ (put

[Haskell-cafe] x86 code generation going wrong?

2006-01-07 Thread Chris Kuklewicz
Hello, I need to ask for some help to test x86 code generation. There is a factor of two runtime difference between the code I am benchmarking on my OS X powerbook G4 (ghc 6.4.1) and shootout's speed on a linux x86 machine (ghc 6.4.1). Could someone else running on x86 test the three versions

Re: [Haskell-cafe] Shootout favoring imperative code

2006-01-07 Thread Sebastian Sylvan
On 1/6/06, Udo Stenzel <[EMAIL PROTECTED]> wrote: > Sebastian Sylvan wrote: > > On 1/5/06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote: > > > There is no need to beat a dead horse, though. This benchmark sets out > > > to test fgets / atoi, and that is all. There are better benchmarks to > > > spen

Re: [Haskell-cafe] Re: Shootout summary

2006-01-07 Thread Donald Bruce Stewart
neubauer: > [EMAIL PROTECTED] (Donald Bruce Stewart) writes: > > >> > Fannkuch entry by Bertram Felgenhauer > >> > Mandelbrot entry > >> > >> I've done some benchmarking of the current entries for fannkuch and > >> mandelbrot, and have proposed final entries for these two tests. > > Using >>= of

Re: [Haskell-cafe] Re: Shootout summary

2006-01-07 Thread Matthias Neubauer
[EMAIL PROTECTED] (Donald Bruce Stewart) writes: >> > Fannkuch entry by Bertram Felgenhauer >> > Mandelbrot entry >> >> I've done some benchmarking of the current entries for fannkuch and >> mandelbrot, and have proposed final entries for these two tests. Using >>= of the list monad in the curre

Re: [Haskell-cafe] Re: Chameneos

2006-01-07 Thread Bulat Ziganshin
Hello Simon, Friday, January 06, 2006, 7:11:41 PM, you wrote: >>>I'm not keen on using explicit unboxed values in these benchmarks, since >>>it looks so ugly. In most cases you can convince GHC to do the unboxing >>>for you, and I'm pretty sure it should be the case here too. Just use >>>ordina