[Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Peter Lund
What do you think the relative speeds are of the six small haskell
programs at the end of this email?

All they do is read from stdin and count the number of spaces they see.
There are two that use strict bytestrings, two that use lazy
bytestrings, and two that use the standard Haskell strings.  Three use a
recursive function with an accumulator parameter and three use a foldl
with a lambda function.

Say the fastest one takes the time 1.  How much time will the others
take?

And how about memory?  How much memory do you think they require?  Let's
say we feed a 150MB(*) file into each of them, how many megabytes do you
think they end up using (as seen from the OS, not in terms of how big
the live heap is)?

I'm going to post full benchmarks + analysis on Wednesday.

-Peter

*) hardddisk megabytes.  The file is 15034 bytes ≈ 143 mebibytes.


PS: For extra credit, what do you think is the peak memory use for this
program when given an input file of 150MB?


{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteString.Lazy.Char8 as B
import GHC.Int (Int64)

-- note that D.BS.Lazy.Char8.length is ByteString - Int64
--   D.BS.C8.length is ByteString - Int
cnt :: B.ByteString - Int64
cnt bs  = B.length (B.filter (== ' ') bs)

main = do s - B.getContents
  print (cnt s)




==
hs/space-bs-c8-acc-1.hs:
{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteString.Char8 as B

cnt :: Int - B.ByteString - Int
cnt !acc bs = if B.null bs
then acc
else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)

main = do s - B.getContents
  print (cnt 0 s)
==
hs/space-bslc8-acc-1.hs:
{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteString.Lazy.Char8 as B

cnt :: Int - B.ByteString - Int
cnt !acc bs = if B.null bs
then acc
else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)

main = do s - B.getContents
  print (cnt 0 s)
==
hs/space-x-acc-1.hs:
{-# LANGUAGE BangPatterns #-}

cnt :: Int - String - Int
cnt !acc bs = if null bs
then acc
else cnt (if head bs == ' ' then acc+1 else acc) (tail bs)

main = do s - getContents
  print (cnt 0 s)
==
hs/space-bs-c8-foldlx-1.hs:
{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteString.Char8 as B

cnt :: B.ByteString - Int
cnt bs  = B.foldl' (\sum c - if c == ' ' then sum+1 else sum) 0 bs

main = do s - B.getContents
  print (cnt s)
==
hs/space-bslc8-foldlx-1.hs:
{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteString.Lazy.Char8 as B

cnt :: B.ByteString - Int
cnt bs  = B.foldl' (\sum c - if c == ' ' then sum+1 else sum) 0 bs

main = do s - B.getContents
  print (cnt s)
==
hs/space-x-foldl.hs:
{-# LANGUAGE BangPatterns #-}

cnt :: String - Int
cnt bs  = foldl (\sum c - if c == ' ' then sum+1 else sum) 0 bs

main = do s - getContents
  print (cnt s)
==


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Software Tools in Haskell

2007-12-15 Thread apfelmus

Benja Fallenstein wrote:

Henning Thielemann wrote:

I remember there was a discussion about how to implement full 'wc' in an
elegant but maximally lazy form, that is counting bytes, words and lines
in one go. Did someone have a nice idea of how to compose the three
counters from implementations of each counter? I'm afraid one cannot
simply use the split and count fragments trick then.


Well, you could rely on catamorphism fusion

  (foldr f1 x1, foldr f2 x2) = foldr (f1 *** f2) (x1,x2)

but that's not so compositional.


Could you turn the folds into scans and use zip3 and last? I.e.,
something like this:


This approach is really clever!


data Triple a b c = Triple !a !b !c deriving Show

countChars :: String - [Int]
countChars = scanl (\n _ - n+1) 0

countChar :: Char - String - [Int]
countChar c = scanl (\n c' - if c == c' then n+1 else n) 0

countLines = countChar '\n'
countWords = countChar ' '

last' [x] = x
last' (x:xs) = x `seq` last' xs

zip3' (x:xs) (y:ys) (z:zs) = Triple x y z : zip3' xs ys zs
zip3' _ _ _ = []


  zipWith3 Triple


wc :: String - Triple Int Int Int
wc xs = last' $ zip3' (countChars xs) (countWords xs) (countLines xs)

main = print . wc = getContents

(or use Data.Strict.Tuple -- but that only has pairs and no zip...)


Slightly simplified (uses BangPatterns):

  import Data.List

  scanl' :: (b - a - b) - b - [a] - [a]
  scanl' f !b [] = [b]
  scanl' f !b (x:xs) = b:scanl' (f b x) xs

  counts :: (a - Bool) - [a] - [Int]
  counts p = scanl' (\n c - if p c then n+1 else n) 0

  wc :: String - (Int,Int,Int)
  wc = last $ zip3 (charc xs) (wordc xs) (linec xs)
 where
 charc = counts (const True)
 wordc = counts (== ' ')
 linec = counts (== '\n')

The  scanl'  basically ensures that the forcing the resulting list spine 
automatically forces the elements. This makes sense to do early and we 
can use normal list functions after that.



Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Jules Bean

Tim Chevalier wrote:

It sounds like Team GHC is thinking about the exact same things you are here:
http://hackage.haskell.org/trac/ghc/wiki/Status/Nov07


Thanks for posting that. I was unaware of that link, and it was very 
interesting reading.


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A Random Question

2007-12-15 Thread Dominic Steinitz
I need to generate distinct arbitrary values for my quickcheck tests and
they don't have to be arbitrary (although that doesn't matter).

No problem I thought, I'll create my own random number generator (which
will not be random at all) and use

 choose :: forall a. (Random a) = (a, a) - Gen a

Here's my code:

 import Test.QuickCheck
 import System.Random
 
 data MyGen = MyGen Int
deriving (Eq, Show)

 myNext :: MyGen - (Int, MyGen)
 myNext (MyGen s1) =
(s1, MyGen (s1 + 1))
 
 -- Assume we will never need this
 mySplit :: MyGen - (MyGen, MyGen)
 mySplit = error No split for predictable random generator
 
 myGenRange :: MyGen - (Int, Int)
 myGenRange (MyGen s1) = (s1, s1)
 
 instance RandomGen MyGen where
next = myNext
split= mySplit
genRange = myGenRange
 
 data Foo = Foo Int
deriving (Eq, Show)
 
 myRandomR :: (Foo, Foo) - MyGen - (Foo, MyGen)
 myRandomR (Foo lo, Foo hi) g =
let (n, g') = next g
   in (Foo n, g')
 
 instance Random Foo where
randomR = myRandomR
random = undefined

But I get

 Supply.hs:33:13:
 Couldn't match expected type `g' against inferred type `MyGen'
   `g' is a rigid type variable bound by
   the type signature for `randomR' at no location info
   Expected type: (Foo, Foo) - g - (Foo, g)
   Inferred type: (Foo, Foo) - MyGen - (Foo, MyGen)
 In the expression: myRandomR
 In the definition of `randomR': randomR = myRandomR
 Failed, modules loaded: none.

I have two questions:

1. Why can't I instantiate a type class with any function I like
provided it fits the type signature?

2. Is this the right approach to generating predictable arbitrary
values? Are there others?

Thanks, Dominic.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Andrew Coppin

Jules Bean wrote:

Tim Chevalier wrote:
It sounds like Team GHC is thinking about the exact same things you 
are here:

http://hackage.haskell.org/trac/ghc/wiki/Status/Nov07


Thanks for posting that. I was unaware of that link, and it was very 
interesting reading.


+1.

Last time I checked, the last status update was from quite a long time 
ago...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Andrew,

Saturday, December 15, 2007, 1:17:56 PM, you wrote:

 http://hackage.haskell.org/trac/ghc/wiki/Status/Nov07
 Thanks for posting that. I was unaware of that link, and it was very
 interesting reading.
 +1.

obviously it's made for forthcoming HCAR but wasn't announced separately

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A Random Question

2007-12-15 Thread Dominic Steinitz
 
 What do you need, i.e., what meaning do you attribute to the words
 predictable and arbitrary? 
 

Apologies - I didn't explain my problem clearly.

I want to say something like:

instance Arbitrary Foo where
   arbitrary = choose (Foo 1, Foo 5)

but the random values are generated by my own random number generator
not the standard one.

Does that make sense? The reason I'm trying to do this is I am
generating random test data but some of it needs to be predictable.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Paul Johnson

Andrew Coppin wrote:

Program with no particular optimisations: 0.35 seconds.
Program with stream fusion [and GHC HEAD]: 0.25 seconds.
Program with stream fusion and ByteString: 0.05 seconds.

Surely you'd have to work pretty hard to get that kind of speed even 
in C. ;-)


...erm, actually no. Somebody sat down and wrote something in five 
minutes that takes 0.005 seconds. Oops!
You may also be paying a fixed cost penalty in GHC run-time 
initialization.  Try increasing N and see what happens.


Paul.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Andrew Coppin

Paul Johnson wrote:

Andrew Coppin wrote:

Program with no particular optimisations: 0.35 seconds.
Program with stream fusion [and GHC HEAD]: 0.25 seconds.
Program with stream fusion and ByteString: 0.05 seconds.

Surely you'd have to work pretty hard to get that kind of speed even 
in C. ;-)


...erm, actually no. Somebody sat down and wrote something in five 
minutes that takes 0.005 seconds. Oops!
You may also be paying a fixed cost penalty in GHC run-time 
initialization.  Try increasing N and see what happens.


Yeah. Hence the we should use something that takes tens of seconds. ;-)

(I suppose I could try writing a nop program and timing it. But 
personally I don't have any way of timing things to that degree of 
accuracy. I understand there are command line tools on Unix that will do 
it, but not here.)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Problem with Gtk2hs

2007-12-15 Thread Andrew Coppin

Ben Franksen wrote:

Andrew Coppin wrote:
  

Uh... or maybe I could just wait until the next binary release. :-}

*runs away*



I can understand that. However, the prudent thing to do is not to upgrade to
a new ghc release until things have settled a bit; especially not if you
want to avoid fixing library bugs (mostly build related) and most
especially if you are on Windows. Ghc-6.6.1 is stable and IME most of the
hackage stuff works out-of-the-box. (Note that Duncan gave you similar
advice, although maybe it got lost beyond all the scary installation tips
concerning gtk2hs under ghc-6.8.1;) Or /is/ there a special reason you need
to use ghc-6.8.1?
  


Not really I guess. I was rather excited about the new debugger, but 
other than that I guess I just like to use the newest version of 
everything. And it would be annoying to have to downgrade now.


Still, it looks like there's an easy workaround for this particular 
issue. (And I'm already explicitly checking array bounds anyway...)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Felipe Lessa
On Dec 15, 2007 10:15 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 (I suppose I could try writing a nop program and timing it. But
 personally I don't have any way of timing things to that degree of
 accuracy. I understand there are command line tools on Unix that will do
 it, but not here.)

Like [1]?

[1] http://shootout.alioth.debian.org/debian/benchmark.php?test=hellolang=all

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Andrew Coppin

Felipe Lessa wrote:

On Dec 15, 2007 10:15 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
  

I suppose I could try writing a nop program and timing it.



Like [1]?

[1] http://shootout.alioth.debian.org/debian/benchmark.php?test=hellolang=all
  


Right. Like that.

So now we have Don's timings for the Haskell program on his PC, Scott's 
timings for the C program on his PC, and the shootout's timings for a 
no-op Haskell program on their PC. I think what I need to do here is run 
a set of timings all on the same PC! ;-)


I'll probably use my laptop. It has SuSE Linux, so it should also have a 
C compiler. (Or if it doesn't, I can easily get one. But I'm pretty sure 
GHC pulls it in as a dependency.)


While I'm here, can somebody tell me the correct command to get a time 
and peak RAM usage printout for a program?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] JOB OFFER / Haskell for commercial projects?

2007-12-15 Thread Wolfgang Jeltsch
Am Samstag, 15. Dezember 2007 13:05 schrieb Paul Johnson:
 […]

 The GHC licence is basically a BSD with attribution. Compiled programs
 include the run-time, so you would just have to include the copyright
 notice somewhere in your documentation. This would also apply to those
 libraries that are shipped with the compiler.

I think, there is some issue with the GMP library which is used for 
implementing the Integer type and which is licensed under the GPL, AFAIK.

 […]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Felipe Lessa
On Dec 15, 2007 11:21 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 While I'm here, can somebody tell me the correct command to get a time
 and peak RAM usage printout for a program?

For how the shootout guys did, see their FAQ [1] and the code of the
benchmarker [2]. It seems that [3] is the file responsible of
executing the tests, but it's pretty huge and my eyes don't really
like reading Perl =).

[1] http://shootout.alioth.debian.org/debian/faq.php
[2] http://alioth.debian.org/scm/?group_id=30402
[3] 
http://alioth.debian.org/plugins/scmcvs/cvsweb.php/shootout/bin/minibench?cvsroot=shootout

Cheers,

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: #haskell works

2007-12-15 Thread Peter Hercek

Andrew Coppin wrote:
(I suppose I could try writing a nop program and timing it. But 
personally I don't have any way of timing things to that degree of 
accuracy. I understand there are command line tools on Unix that will do 
it, but not here.)


You can try for example this one http://www.pc-tools.net/win32/ptime/
 to measure times better on windows. I tried the above prg few years ago
 and it seemed to work. If you do not mind installing cygwin then you
 can get time command from it.

The only problem is that both ptime and cygwin time do not add times
 of child processes to the result. Unix tools do that by default (since
 child accounting info is added to parent process if the child is
 waited for).

If you want to add children time to your result you probably need to
 write your own utility for win32 timing. It should be something like
 100 lines of C code. See QueryInformationJobObject win32 api function
 to start. I know only one commercial tool which can take children
 time into account on windows. If you would write it and decide to
 release it under a free license, let me know :)

Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Duncan Coutts

On Sat, 2007-12-15 at 09:25 +0100, Peter Lund wrote:
 What do you think the relative speeds are of the six small haskell
 programs at the end of this email?

Ok, I presume this is a guessing game and we're supposed to just look at
the code without running and timing them.

 All they do is read from stdin and count the number of spaces they see.
 There are two that use strict bytestrings, two that use lazy
 bytestrings, and two that use the standard Haskell strings.  Three use a
 recursive function with an accumulator parameter and three use a foldl
 with a lambda function.
 
 Say the fastest one takes the time 1.  How much time will the others
 take?
 
 And how about memory?  How much memory do you think they require?  Let's
 say we feed a 150MB(*) file into each of them, how many megabytes do you
 think they end up using (as seen from the OS, not in terms of how big
 the live heap is)?
 
 I'm going to post full benchmarks + analysis on Wednesday.

Right'o. I'll have a go. Lets see if I can't embarrass myself with being
completely inaccurate.


 PS: For extra credit, what do you think is the peak memory use for this
 program when given an input file of 150MB?

Ok.

 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Lazy.Char8 as B
 import GHC.Int (Int64)
 
 -- note that D.BS.Lazy.Char8.length is ByteString - Int64
 --   D.BS.C8.length is ByteString - Int

Yes, because strict bytestring cannot be bigger than the size of virtual
memory and with ghc at least, Int tracks the size of the machine
pointer.

 cnt   :: B.ByteString - Int64
 cnt bs= B.length (B.filter (== ' ') bs)
 
 main = do s - B.getContents
 print (cnt s)

Hmm. So that should work in constant memory, a few 64 chunks at once.
I'd expect this to be pretty fast.

 
 
 
 ==
 hs/space-bs-c8-acc-1.hs:
 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Char8 as B
 
 cnt   :: Int - B.ByteString - Int
 cnt !acc bs = if B.null bs
   then acc
   else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)
 
 main = do s - B.getContents
 print (cnt 0 s)

This uses strict bytestrings so will use at least 150Mb and that'll make
it a good deal slower. In fact it'll be worse than that since
getContents does not know in advance how big the input will be so it has
to play the doubling and copying game. So it'll end up copying all the
data roughly twice. cnt is strict and tail recursive so that shouldn't
be any problem, though it's probably not as fast as the first length .
filter since head, tail, null all have to do bounds checks.

 ==
 hs/space-bslc8-acc-1.hs:
 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Lazy.Char8 as B
 
 cnt   :: Int - B.ByteString - Int
 cnt !acc bs = if B.null bs
   then acc
   else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)
 
 main = do s - B.getContents
 print (cnt 0 s)

For the same reason as above, I'd expect this cnt to be slower than
B.length . B.filter (== ' ')

 ==
 hs/space-x-acc-1.hs:
 {-# LANGUAGE BangPatterns #-}
 
 cnt   :: Int - String - Int
 cnt !acc bs = if null bs
   then acc
   else cnt (if head bs == ' ' then acc+1 else acc) (tail bs)
 
 main = do s - getContents
 print (cnt 0 s)

Lazy, so constant memory use, but much higher constant factors due to
using String.

 ==
 hs/space-bs-c8-foldlx-1.hs:
 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Char8 as B
 
 cnt   :: B.ByteString - Int
 cnt bs= B.foldl' (\sum c - if c == ' ' then sum+1 else sum) 0 bs
 
 main = do s - B.getContents
 print (cnt s)

This is of course still strict so that's going to make the reading slow.

This is a manually fused B.length . B.filter (== ' ') which hopefully is
the same speed as the automatically fused one if the fusion is working
ok. If not, then the B.length . B.filter (== ' ') will be doing a extra
copy, and memory writes are expensive.

 ==
 hs/space-bslc8-foldlx-1.hs:
 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Lazy.Char8 as B
 
 cnt   :: B.ByteString - Int
 cnt bs= B.foldl' (\sum c - if c == ' ' then sum+1 else sum) 0 bs
 
 main = do s - B.getContents
 print (cnt s)

As above but now in constant memory space.

 ==
 hs/space-x-foldl.hs:
 {-# LANGUAGE BangPatterns #-}
 
 cnt   :: String - Int
 cnt bs= foldl (\sum c - if c == ' ' then sum+1 else sum) 0 bs
 
 main = do s - getContents
 print (cnt s)

Oh, no! not foldl that's a killer.


Ok, so best way to summarise I think is to organise by data type since I
think that'll dominate.

So I think the lazy bytestring versions will be fastest due to having
the best memory access patterns and doing the least copying. I think the
foldl's will 

Re: Re[4]: [Haskell-cafe] #haskell works

2007-12-15 Thread Tim Chevalier
On 12/15/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 Hello Tim,

 Saturday, December 15, 2007, 7:10:26 AM, you wrote:

  with support of loop unrolling,

  GHC calls this inlining.

 1. loop unrolling means generating several iterations of loop body,
 so that, say, 100 iterations of *p++=*q++ becomes 25 iterations of
 *p++=*q++; *p++=*q++; *p++=*q++; *p++=*q++;


I know what loop unrolling means. In a pure functional language, it
reduces to inlining, because recursion is used instead of loops, and
the inliner can do the job of inlining (a fixed number of) iterations
of a recursive function -- I don't know if it does this now, but it
would be easy to implement.  You don't have to believe me -- read
section 4.6 of the inliner paper:
http://research.microsoft.com/~simonpj/Papers/inlining/

 2. actually, ghc can't inline tail-recursive functions at all
 (although i don't checked this after 6.4)


It may be that GHC *doesn't* inline tail-recursive functions, but as I
pointed out above (which I'm just getting directly from the paper), it
would be easy to flip a switch and let it inline a fixed number of
iterations of them.

 there are also many more optimization tricks. i don't think that
 modern compiler with optimization level comparable to gcc can be
 delivered without many man-years of development


I think that's an awfully definite statement to make, given that C and
Haskell are very different languages, given how many high-level
optimizations are possible in Haskell that aren't in C, and given how
much higher programmer productivity is in Haskell than C. For example,
as above, loop unrolling turns out to be just a special case of
inlining. That's not true in C. The simplicity of Haskell (or rather,
Core) means it's easy to implement a lot of things with a great deal
of generality, an advantage that gcc doesn't have.

Or, I mean, feel free to insist things are impossible, but try not to
stand in the way of the people who are doing them while you say so.
:-)

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
It's easy to consider women more emotional than men when you don't
consider rage to be an emotion. -- Brenda Fine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Random Question

2007-12-15 Thread Paul Johnson

Dominic Steinitz wrote:

I want to say something like:

instance Arbitrary Foo where
   arbitrary = choose (Foo 1, Foo 5)

but the random values are generated by my own random number generator
not the standard one.

Does that make sense? The reason I'm trying to do this is I am
generating random test data but some of it needs to be predictable

It makes sense, but its not possible.  The generate function has the type:

*generate* :: Int 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3AInt 
- StdGen 
http://www.haskell.org/ghc/docs/latest/html/libraries/random/System-Random.html#t%3AStdGen 
- Gen 
http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickCheck.html#t%3AGen 
a - a


Unfortunately for your purpose you would need:

*generate* :: (RandomGen g) = Int 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3AInt 
- g - Gen 
http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickCheck.html#t%3AGen 
a - a


Take a look at SmallCheck.  It might be more suited to your requirement 
anyway.


Paul.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] JOB OFFER / Haskell for commercial projects?

2007-12-15 Thread Duncan Coutts

On Sat, 2007-12-15 at 14:29 +0100, Wolfgang Jeltsch wrote:
 Am Samstag, 15. Dezember 2007 13:05 schrieb Paul Johnson:
  […]
 
  The GHC licence is basically a BSD with attribution. Compiled programs
  include the run-time, so you would just have to include the copyright
  notice somewhere in your documentation. This would also apply to those
  libraries that are shipped with the compiler.
 
 I think, there is some issue with the GMP library which is used for 
 implementing the Integer type and which is licensed under the GPL, AFAIK.

It's the LGPL not the GPL. See http://gmplib.org/

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Random Question

2007-12-15 Thread Dominic Steinitz
Paul Johnson wrote:
 Dominic Steinitz wrote:

 Unfortunately for your purpose you would need:
 
 *generate* :: (RandomGen g) = Int
 http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3AInt
 - g - Gen
 http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickCheck.html#t%3AGen
 a - a

Thanks - rather what I thought.

This seems to do the trick using a state monad but it doesn't look pretty.

import Test.QuickCheck
import Control.Monad.State

data Baz = Baz String Int
   deriving (Eq, Show)

g :: MonadState Int m = m (Gen Int)
g =
   do x - get
  put (x + 1)
  return (return x)

f :: MonadState Int m = Int - m (Gen [Baz])
f 0 = return (return [])
f n =
   do x - g
  xs - f (n - 1)
  let z = do u - x
 us - xs
 v - arbitrary
 return ((Baz (t ++ (show u)) v):us)
  return z


*Main let (q,p) = runState (f 10) 1 in sample q
[Baz t1 (-1),Baz t2 0,Baz t3 0,Baz t4 (-1),Baz t5 1,Baz t6
1,Baz t7 1,Baz t8 1,Baz t9 1,Baz t10 1]
[Baz t1 0,Baz t2 2,Baz t3 (-2),Baz t4 (-2),Baz t5 (-1),Baz
t6 0,Baz t7 1,Baz t8 2,Baz t9 (-2),Baz t10 (-2)]

This gives me what I wanted: distinct (and in this case predictable)
names and random values.

 
 Take a look at SmallCheck.  It might be more suited to your requirement
 anyway.
 

I will do so now.

Thanks, Dominic.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Tim Chevalier
On 12/15/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 (I suppose I could try writing a nop program and timing it. But
 personally I don't have any way of timing things to that degree of
 accuracy. I understand there are command line tools on Unix that will do
 it, but not here.)

Try the -Rghc-timing flag.

Cheers,
Tim

--
Tim Chevalier * catamorphism.org * Often in error, never in doubt
and there's too much darkness in an endless night to be afraid of the
way we feel -- Bob Franke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: New slogan for haskell.org

2007-12-15 Thread apfelmus

Henning Thielemann wrote:

apfelmus wrote:


gwern wrote:

Now, the Main Page on haskell.org is not protected, so I could just edit
in one of the better descriptions proposed, but as in my Wikipedia editing,
I like to have consensus especially for such visible changes.


Hey, why has the front-page already been changed then? I don't like
neither this nor the new slogan.


Edit war!


Yarr, bring up the guns! Y-rifle, fire!

http://ellemose.dina.kvl.dk/cgi-bin/sestoft/lamreduce?action=normalizeexpression=%5Clamb.%28%5Cx.%5Cf.f%28x+x+f%29%29+%28%5Cx.%5Cf.f%28x+x+f%29%29+%28%5Cf.%5Cda.f%29evalorder=normal+order

Goodstein gun, fire!

import Data.Tree

type Number = Forest Integer

zero = []; one = [Node 1 zero]; two = [Node 1 one]  -- (shortened) 
hereditary
three = one++two; four = [Node 1 two]   -- base 2 
representation


subtractOne p (Node 1 []:xs) = xs
subtractOne p (Node a []:xs) = Node (a-1) []:xs
subtractOne p (Node 1 k :xs) = let k' = subtractOne p k in
   subtractOne p [Node 1 k'] ++ Node 
(p-1) k':xs
subtractOne p (Node a k :xs) = subtractOne p [Node 1 k ] ++ Node 
(a-1) k :xs


goodstein !p n = if null n then [] else n:goodstein (p+1) 
(subtractOne (p+1) n)

goodsteingun n = concat $ lamb:map (const da) (goodstein 2 n)

  goodsteingun three
 lambdadadadadada
  goodsteingun four
 lambdadadadadadadadadadadadadadadadadadadadadada[...]

Will it ever cease?


Regards,
apfelmus




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Peter Lund
On Sat, 2007-12-15 at 14:34 +, Duncan Coutts wrote:

 Ok, I presume this is a guessing game and we're supposed to just look at
 the code without running and timing them.

Precisely :)

  All they do is read from stdin and count the number of spaces they see.
  There are two that use strict bytestrings, two that use lazy
  bytestrings, and two that use the standard Haskell strings.  Three use a
  recursive function with an accumulator parameter and three use a foldl
  with a lambda function.
  
  Say the fastest one takes the time 1.  How much time will the others
  take?
  
  And how about memory?  How much memory do you think they require?  Let's
  say we feed a 150MB(*) file into each of them, how many megabytes do you
  think they end up using (as seen from the OS, not in terms of how big
  the live heap is)?
  
  I'm going to post full benchmarks + analysis on Wednesday.
 
 Right'o. I'll have a go. Lets see if I can't embarrass myself with being
 completely inaccurate.

Thanks for biting!

You were, thankfully, only almost completely inaccurate ;)

  PS: For extra credit, what do you think is the peak memory use for this
  program when given an input file of 150MB?

 Hmm. So that should work in constant memory, a few 64 chunks at once.
 I'd expect this to be pretty fast.

You are right about the speed.
Can you guess a number in kilobytes?

  
  
  
  ==
  hs/space-bs-c8-acc-1.hs:
  {-# LANGUAGE BangPatterns #-}
  
  import qualified Data.ByteString.Char8 as B
  
  cnt :: Int - B.ByteString - Int
  cnt !acc bs = if B.null bs
  then acc
  else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)
  
  main = do s - B.getContents
print (cnt 0 s)
 
 This uses strict bytestrings so will use at least 150Mb and that'll make
 it a good deal slower. In fact it'll be worse than that since
 getContents does not know in advance how big the input will be so it has
 to play the doubling and copying game. So it'll end up copying all the
 data roughly twice. cnt is strict and tail recursive so that shouldn't
 be any problem, though it's probably not as fast as the first length .
 filter since head, tail, null all have to do bounds checks.

You are right about the memory.  It is actually slightly faster than the
extra credit (length/filter combination) above.

  ==
  hs/space-bslc8-acc-1.hs:
  {-# LANGUAGE BangPatterns #-}
  
  import qualified Data.ByteString.Lazy.Char8 as B
  
  cnt :: Int - B.ByteString - Int
  cnt !acc bs = if B.null bs
  then acc
  else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)
  
  main = do s - B.getContents
print (cnt 0 s)
 
 For the same reason as above, I'd expect this cnt to be slower than
 B.length . B.filter (== ' ')

It is slower but not for the same reason as above.

  ==
  hs/space-x-acc-1.hs:
  {-# LANGUAGE BangPatterns #-}
  
  cnt :: Int - String - Int
  cnt !acc bs = if null bs
  then acc
  else cnt (if head bs == ' ' then acc+1 else acc) (tail bs)
  
  main = do s - getContents
print (cnt 0 s)
 
 Lazy, so constant memory use, but much higher constant factors due to
 using String.

Spot on.

  ==
  hs/space-bs-c8-foldlx-1.hs:
  {-# LANGUAGE BangPatterns #-}
  
  import qualified Data.ByteString.Char8 as B
  
  cnt :: B.ByteString - Int
  cnt bs  = B.foldl' (\sum c - if c == ' ' then sum+1 else sum) 0 bs
  
  main = do s - B.getContents
print (cnt s)
 
 This is of course still strict so that's going to make the reading slow.

Nope.

 This is a manually fused B.length . B.filter (== ' ') which hopefully is
 the same speed as the automatically fused one if the fusion is working
 ok. If not, then the B.length . B.filter (== ' ') will be doing a extra
 copy, and memory writes are expensive.
 
  ==
  hs/space-bslc8-foldlx-1.hs:
  {-# LANGUAGE BangPatterns #-}
  
  import qualified Data.ByteString.Lazy.Char8 as B
  
  cnt :: B.ByteString - Int
  cnt bs  = B.foldl' (\sum c - if c == ' ' then sum+1 else sum) 0 bs
  
  main = do s - B.getContents
print (cnt s)
 
 As above but now in constant memory space.

Nope.

  ==
  hs/space-x-foldl.hs:
  {-# LANGUAGE BangPatterns #-}
  
  cnt :: String - Int
  cnt bs  = foldl (\sum c - if c == ' ' then sum+1 else sum) 0 bs
  
  main = do s - getContents
print (cnt s)
 
 Oh, no! not foldl that's a killer.

You think it's worse than the program just above?

 
 Ok, so best way to summarise I think is to organise by data type since I
 think that'll dominate.
 
 So I think the lazy bytestring versions will be fastest due to having
 the best memory access patterns and doing the least copying. I think the
 foldl's will be faster than the explicit accumulators due to having
 fewer bounds checks.
 
 space-bslc8-foldlx-1
 

[Haskell-cafe] Re: #haskell works

2007-12-15 Thread Peter Hercek

Tim Chevalier wrote:

Try the -Rghc-timing flag.


Interesting, that one does not work in my program compiled with
 ghc 6.8.1 (looks like ghc runtime does not consume it but passes
 it to my haskell code). +RTS -tstderr works but its usability is
 limited since it provides only elapsed time and not the process
 cpu times.

Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Fw: hdbc odbc also crashes on 6.8.2 Re: [Haskell-cafe] HDBC-ODBC crashes on ghc 6.8

2007-12-15 Thread Olivier Boudry
On Dec 14, 2007 12:37 PM, Thomas Hartman [EMAIL PROTECTED] wrote:



 I just tried HDBC-ODBC on 6.8.2, but it still crashes. Works on 6.6.1.

 thomas.


Hi Thomas,

I tried to compile your minimal app on 6.8.2 and get the following result.

C:\Tempghc --make TestHDBC.hs
Linking TestHDBC.exe ...
C:\Program Files\Haskell\HDBC-
odbc-1.1.3.0\ghc-6.8.2/libHSHDBC-odbc-1.1.3.0.a(Co
nnection.o)(.text+0x52c):fake: undefined reference to `SQLAllocHandle'
C:\Program Files\Haskell\HDBC-
odbc-1.1.3.0\ghc-6.8.2/libHSHDBC-odbc-1.1.3.0.a(Co
nnection.o)(.text+0x5b8):fake: undefined reference to `SQLSetEnvAttr'
... (long list of undefined references)...

When running it using ghc -e main it gives no error, but when compiling I
get those undefined reference errors. The functions listed here are defined
in ghc-lib\libodbc32.a and using filemon I could see that the library is
found and opened from ld.exe during linking. I don't understand why it
cannot link to those functions.

Olivier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: #haskell works

2007-12-15 Thread Tim Chevalier
On 12/15/07, Peter Hercek [EMAIL PROTECTED] wrote:
 Tim Chevalier wrote:
  Try the -Rghc-timing flag.

 Interesting, that one does not work in my program compiled with
   ghc 6.8.1 (looks like ghc runtime does not consume it but passes
   it to my haskell code). +RTS -tstderr works but its usability is
   limited since it provides only elapsed time and not the process
   cpu times.


Sorry, my mistake -- it's an RTS option, so:

./program +RTS -Rghc-timing -RTS

and I guess you have to compile with -prof.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
Live fast, love hard, and wear corrective lenses if you need them.
--Webb Wilder
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Random Question

2007-12-15 Thread Harald Holtmann
Dominic Steinitz schrieb:
 What do you need, i.e., what meaning do you attribute to the words
 predictable and arbitrary? 

 
 Apologies - I didn't explain my problem clearly.
 
 I want to say something like:
 
 instance Arbitrary Foo where
arbitrary = choose (Foo 1, Foo 5)
 
 but the random values are generated by my own random number generator
 not the standard one.
 
 Does that make sense? The reason I'm trying to do this is I am
 generating random test data but some of it needs to be predictable.

When I work with QuickCheck, it often finds some interesting corner
cases. I prefer to solve this one problem before further testing, so I
use a little wrapper around QuickCheck to be able to reproduce a
specific test:

code

import Test.QuickCheck hiding (test)
import qualified Test.QuickCheck as QC (test)

test prop =
  do getStdGen = print
 QC.test prop

-- for repeatable tests
testRnd prop r1 r2 =
  do setStdGen . read $ show r1 ++   ++ show r2
 QC.test prop

/code

'test' simply dumps the current generator (show as two numbers) and one
can use these two numbers with 'testRnd' to repeat the test with exactly
the same data.
Perhaps this technique is useful for your problem.

Cheers,
Harald





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] getMessage function in Win32 API

2007-12-15 Thread Eric

Dear all,

In the Graphics.Win32.Window package there is a function getMessage 
takes a value of type LPMSG. How can I construct a value of LPMSG so 
that I can call the function?



E.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: #haskell works

2007-12-15 Thread Peter Hercek

Tim Chevalier wrote:

On 12/15/07, Peter Hercek [EMAIL PROTECTED] wrote:

Tim Chevalier wrote:

Try the -Rghc-timing flag.

Interesting, that one does not work in my program compiled with
  ghc 6.8.1 (looks like ghc runtime does not consume it but passes
  it to my haskell code). +RTS -tstderr works but its usability is
  limited since it provides only elapsed time and not the process
  cpu times.



Sorry, my mistake -- it's an RTS option, so:

./program +RTS -Rghc-timing -RTS

and I guess you have to compile with -prof.



I guess it is just buggy in 6.8.1.
That option does not seem to work, not even as an RTS option
 and even when I compile with -prof -auto-all.
But the user guide states that the result should be the same
 as with +RTS -tstderr and if so then it is not that
 interesting (since cpu times are missing). Btw, +RTS -tstderr
 works without -prof too, which is nice :)
I liked the idea that ghc generated exe can report its times
 too (I meant also cpu times and not only the elapsed time)
 but external programs work well for this too, so never mind.

Thanks,
Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[6]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Tim,

Saturday, December 15, 2007, 5:35:03 PM, you wrote:

 the inliner can do the job of inlining (a fixed number of) iterations
 of a recursive function -- I don't know if it does this now, but it
 would be easy to implement.

 It may be that GHC *doesn't* inline tail-recursive functions, but as I
 pointed out above (which I'm just getting directly from the paper), it
 would be easy

i see your point - it's easy to implement everything in GHC. probably
its authors was sleeping last 15 years :)

 as above, loop unrolling turns out to be just a special case of
 inlining.

and ghc was so genuine that it was implemented general case without
implementing special one :)

 That's not true in C. The simplicity of Haskell (or rather,
 Core) means it's easy to implement a lot of things with a great deal
 of generality, an advantage that gcc doesn't have.

Core language has the same complexity for generating good code as C, C-- or LLVM

 Or, I mean, feel free to insist things are impossible, but try not to
 stand in the way of the people who are doing them while you say so.
 :-)

you may believe in what you want. i prefer to say about real
situation. if it will be possible to quickly write good Haskell
compiler, it was be written many years ago

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Robin Green
On Sat, 15 Dec 2007 21:46:43 +0300
Bulat Ziganshin [EMAIL PROTECTED] wrote:
 you may believe in what you want. i prefer to say about real
 situation. if it will be possible to quickly write good Haskell
 compiler, it was be written many years ago

No-one is writing a commercial Haskell compiler yet (although there is
at least one commercial Haskell-like language). What I mean is, the
amount of commercial-oriented funding spent on GHC (as opposed to
the research-oriented funding spent by Microsoft Research and various
research bodies) is, as far as I know, zero. Incentives matter. If
there were a commercial Haskell compiler, maybe we would see faster
progress.
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Neil Mitchell
Hi

 No-one is writing a commercial Haskell compiler yet (although there is
 at least one commercial Haskell-like language). What I mean is, the
 amount of commercial-oriented funding spent on GHC (as opposed to
 the research-oriented funding spent by Microsoft Research and various
 research bodies) is, as far as I know, zero. Incentives matter. If
 there were a commercial Haskell compiler, maybe we would see faster
 progress.

It isn't just about money. It's also about ideas, luck and randomly
bumping into people. I am sure there is a great strategy for making
really fast Haskell compilers, and I am sure at some point we'll
figure out what it is.

I agree with Bulat that Haskell has, if anything, even better
optimisation potential than something like C. With Haskell you can do
the crazy high-level optimisations that things like C would demand
really advanced alias-analysis. Compare this to low-level
optimisations which in Haskell require strictness analysis but in C
are easy. At some point high-level will become more important than
low-level, when it does, we win :-)

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Robin,

Saturday, December 15, 2007, 9:54:43 PM, you wrote:

 you may believe in what you want. i prefer to say about real
 situation. if it will be possible to quickly write good Haskell
 compiler, it was be written many years ago

 No-one is writing a commercial Haskell compiler yet (although there is
 at least one commercial Haskell-like language). What I mean is, the
 amount of commercial-oriented funding spent on GHC (as opposed to
 the research-oriented funding spent by Microsoft Research and various
 research bodies) is, as far as I know, zero. Incentives matter. If
 there were a commercial Haskell compiler, maybe we would see faster
 progress.

yes, it's one of my points. among complexity of generating efficient
code for high-level language, there are just too small resources spent
here compared to icc/gcc/msvc. i don't think that good Haskell
compiler (for simple loops) is impossible, i just don't see chances to
get it in reality

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Neil,

Saturday, December 15, 2007, 10:07:54 PM, you wrote:

 I agree with Bulat that Haskell has, if anything, even better
 optimisation potential than something like C. With Haskell you can do
 the crazy high-level optimisations that things like C would demand
 really advanced alias-analysis.

i think that this ability is already implemented in GHC. but low-level
code generation, STG-to-Asm level, is very simple and may be compared
only with 20-year old C compilers like MSC 5.1


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Andrew Coppin

Neil Mitchell wrote:

Hi
  
I agree with Bulat that Haskell has, if anything, even better

optimisation potential than something like C. With Haskell you can do
the crazy high-level optimisations that things like C would demand
really advanced alias-analysis. Compare this to low-level
optimisations which in Haskell require strictness analysis but in C
are easy. At some point high-level will become more important than
low-level, when it does, we win :-)
  


I had this conversation where Mr C++ basically said that my code 
implements 3 loops and it's not possible to optimise that into just 1 
loop like the C program is doing. Then I (or rather, Don) demonstrated 
that the stream fusion library *has* optimised it into just 2 loops. 
(Apparently the library isn't 100% complete as yet.)


I liken transformations like this to the sort of high-level 
optimisations that a database engine might do given an SQL statement. An 
SQL SELECT certainly *looks* just like a loop construct. But it isn't; 
it declares the result, not the algorithm, freeing the database to use 
*any* algorithm that produces the right answer. The result is that, as 
is well known, databases are supremely good at executing SQL queries 
blisteringly fast. When I see the compiler turn 3 loops into 2 by using 
algebraic properties of the program source code, that's how I think of it.


Hmm, perhaps to really show this off, we need a more complicated 
program. Something that would be just too hard to implement as 1 loop in 
C, but is easy for the GHC optimiser to build. I shall meditate on this 
further...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Don Stewart
andrewcoppin:
 Neil Mitchell wrote:
 Hi
   
 I agree with Bulat that Haskell has, if anything, even better
 optimisation potential than something like C. With Haskell you can do
 the crazy high-level optimisations that things like C would demand
 really advanced alias-analysis. Compare this to low-level
 optimisations which in Haskell require strictness analysis but in C
 are easy. At some point high-level will become more important than
 low-level, when it does, we win :-)
   
 
 I had this conversation where Mr C++ basically said that my code 
 implements 3 loops and it's not possible to optimise that into just 1 
 loop like the C program is doing. Then I (or rather, Don) demonstrated 
 that the stream fusion library *has* optimised it into just 2 loops. 
 (Apparently the library isn't 100% complete as yet.)

Right, we haven't bothered with streaming versions of 'words'. 
However, the maximumBy and map happily fuse into a single loop.
   
 Hmm, perhaps to really show this off, we need a more complicated 
 program. Something that would be just too hard to implement as 1 loop in 
 C, but is easy for the GHC optimiser to build. I shall meditate on this 
 further...

Do you have the single loop C program, btw? I'd be curious to see if
this is really feasible. It would have to do the buffering, tokenising
and accumulating in one go. I'd imagine it is a bit hairy.

And, it should not significantly outperform, say, a bytestring version.
If it does, I'd like to see that.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Don Stewart
firefly:
 What do you think the relative speeds are of the six small haskell
 programs at the end of this email?
 
 All they do is read from stdin and count the number of spaces they see.
 There are two that use strict bytestrings, two that use lazy
 bytestrings, and two that use the standard Haskell strings.  Three use a
 recursive function with an accumulator parameter and three use a foldl
 with a lambda function.
 
 Say the fastest one takes the time 1.  How much time will the others
 take?
 
 And how about memory?  How much memory do you think they require?  Let's
 say we feed a 150MB(*) file into each of them, how many megabytes do you
 think they end up using (as seen from the OS, not in terms of how big
 the live heap is)?
 
 I'm going to post full benchmarks + analysis on Wednesday.

How are you compiling these programs, by the way?  ghc-6.8.2 -O2  ?
(-O2 is required for bytestrings :)

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Don,

Saturday, December 15, 2007, 10:57:02 PM, you wrote:

 Do you have the single loop C program, btw? I'd be curious to see if
 this is really feasible. It would have to do the buffering, tokenising
 and accumulating in one go. I'd imagine it is a bit hairy.

for (int n; n = read (0, buf, 32768);) {
  for (char *p=buf,*end=buf+n;;)
while (*p++==' ') if(p==end) goto end;
while (*p++!=' ') if(p==end) goto end;
words++;
  }
  end:;
}

 And, it should not significantly outperform, say, a bytestring version.
 If it does, I'd like to see that.

you are welcome :)

OPT_FLAGS   = -O3 -march=pentiumpro -mtune=pentiumpro \
  -fomit-frame-pointer -fstrict-aliasing \
  -ffast-math -fforce-addr -funroll-loops \
  -fno-exceptions -fno-rtti


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Don Stewart
bulat.ziganshin:
 Hello Don,
 
 Saturday, December 15, 2007, 10:57:02 PM, you wrote:
 
  Do you have the single loop C program, btw? I'd be curious to see if
  this is really feasible. It would have to do the buffering, tokenising
  and accumulating in one go. I'd imagine it is a bit hairy.
 
 for (int n; n = read (0, buf, 32768);) {
   for (char *p=buf,*end=buf+n;;)
 while (*p++==' ') if(p==end) goto end;
 while (*p++!=' ') if(p==end) goto end;
 words++;
   }
   end:;
 }

How many loops is that, Bulat? :)

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Don Stewart
dons:
 bulat.ziganshin:
  Hello Don,
  
  Saturday, December 15, 2007, 10:57:02 PM, you wrote:
  
   Do you have the single loop C program, btw? I'd be curious to see if
   this is really feasible. It would have to do the buffering, tokenising
   and accumulating in one go. I'd imagine it is a bit hairy.
  
  for (int n; n = read (0, buf, 32768);) {
for (char *p=buf,*end=buf+n;;)
  while (*p++==' ') if(p==end) goto end;
  while (*p++!=' ') if(p==end) goto end;
  words++;
}
end:;
  }
 

Oh, this isn't the original program, either. You need to find the
longest word and print it. Not count the words.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] JOB OFFER / Haskell for commercial projects?

2007-12-15 Thread Bit Connor
On Dec 15, 2007 4:40 PM, Duncan Coutts [EMAIL PROTECTED] wrote:
 On Sat, 2007-12-15 at 14:29 +0100, Wolfgang Jeltsch wrote:
  [...]
 
  I think, there is some issue with the GMP library which is used for
  implementing the Integer type and which is licensed under the GPL, AFAIK.

 It's the LGPL not the GPL. See http://gmplib.org/

When GHC compiles a haskell program, it seems to statically link in
libgmp. I don't believe that libgmp's license has a static linking
exception. Therefore it would seem that the resulting haskell program
must be distributed only under the terms of the LGPL(either providing
providing the full source of your haskell program, or providing your
object files).

Or am I missing something?

Thanks,
Bit
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] JOB OFFER / Haskell for commercial projects?

2007-12-15 Thread Don Stewart
bit:
 On Dec 15, 2007 4:40 PM, Duncan Coutts [EMAIL PROTECTED] wrote:
  On Sat, 2007-12-15 at 14:29 +0100, Wolfgang Jeltsch wrote:
   [...]
  
   I think, there is some issue with the GMP library which is used for
   implementing the Integer type and which is licensed under the GPL, AFAIK.
 
  It's the LGPL not the GPL. See http://gmplib.org/
 
 When GHC compiles a haskell program, it seems to statically link in
 libgmp. I don't believe that libgmp's license has a static linking
 exception. Therefore it would seem that the resulting haskell program
 must be distributed only under the terms of the LGPL(either providing
 providing the full source of your haskell program, or providing your
 object files).
 
 Or am I missing something?

Yep :)

GHC doesn't statically link libgmp, unless you build it to do so.
By default it will use your dynamically linked libgmp.

$ ldd `which xmonad`
/home/dons/bin/xmonad:
StartEnd  Type Open Ref GrpRef Name
  exe  10   0  /home/dons/bin/xmonad
468d5000 46cd7000 rlib 01   0  
/usr/X11R6/lib/libXinerama.so.5.0
44a55000 44e66000 rlib 02   0  
/usr/X11R6/lib/libXext.so.10.0
4cf4f000 4d45b000 rlib 03   0  
/usr/X11R6/lib/libX11.so.10.0
4bbff000 4c008000 rlib 01   0  
/usr/lib/libutil.so.11.0
4d45b000 4d874000 rlib 01   0  /usr/lib/libm.so.2.3
--4c485000 4c8c1000 rlib 01   0  
/usr/local/lib/libgmp.so.7.0
4a5f 4aac2000 rlib 01   0  /usr/lib/libc.so.42.0
42934000 42d37000 rlib 03   0  
/usr/X11R6/lib/libXau.so.9.0
4fe36000 5023b000 rlib 03   0  
/usr/X11R6/lib/libXdmcp.so.9.0
41b0 41b0 rtld 01   0  /usr/libexec/ld.so

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Don,

Saturday, December 15, 2007, 11:28:00 PM, you wrote:

   Do you have the single loop C program, btw? I'd be curious to see if

 Oh, this isn't the original program, either. You need to find the
 longest word and print it. Not count the words.

i can't understand what you mean by single-loop program? my code does
one pass through the data without generating any intermediate data
structures and i think that it's not worse than output of stream
fusion

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] JOB OFFER / Haskell for commercial projects?

2007-12-15 Thread Bulat Ziganshin
Hello Don,

Saturday, December 15, 2007, 11:55:04 PM, you wrote:

 When GHC compiles a haskell program, it seems to statically link in
 libgmp.

 GHC doesn't statically link libgmp, unless you build it to do so.
 By default it will use your dynamically linked libgmp.

at least, on Windows this should be true

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Don Stewart
bulat.ziganshin:
 Hello Don,
 
 Saturday, December 15, 2007, 11:28:00 PM, you wrote:
 
Do you have the single loop C program, btw? I'd be curious to see if
 
  Oh, this isn't the original program, either. You need to find the
  longest word and print it. Not count the words.
 
 i can't understand what you mean by single-loop program? my code does
 one pass through the data without generating any intermediate data
 structures and i think that it's not worse than output of stream
 fusion

Yes, its very nice! That is the kind of code I'd *hope* to produce from
a series of fused loops! A bunch of little loop bodies alternative
control.

I'm actually more interested in Andrew's mysterious 10x faster C
program, someone provided to him. It solved the original problem of
finding the longest word in the dictionary. (So slightly more complex).

I'd expect a 2-3x worse bytestring program, in the worst case. So the
10x figure has been curious.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Andrew Coppin

Don Stewart wrote:

andrewcoppin:
  

(Apparently the library isn't 100% complete as yet.)



Right, we haven't bothered with streaming versions of 'words'. 
However, the maximumBy and map happily fuse into a single loop.
  


Indeed. And hopefully when words gets implemented, we will have One Loop 
to rule them all... er... well you know what I mean.


Hmm, perhaps to really show this off, we need a more complicated 
program. Something that would be just too hard to implement as 1 loop in 
C, but is easy for the GHC optimiser to build. I shall meditate on this 
further...



Do you have the single loop C program, btw? I'd be curious to see if
this is really feasible. It would have to do the buffering, tokenising
and accumulating in one go. I'd imagine it is a bit hairy.

And, it should not significantly outperform, say, a bytestring version.
If it does, I'd like to see that.
  


First version:

n = 0;
while( n  FILE_SIZE )
{
while( n  FILE_SIZE   file[n++] == ' ' ); wStart = n;
while( n  FILE_SIZE   file[n++] != ' ' ); wLength = n - wStart;
if( wLength  strlen( longestString ) )  strncpy( longestString , file 
+ wStart , wLength );

}

Takes 0.016 seconds to process a 2.4 MB file. [But not the same one Don 
used.]


Then Mr C++ looked at it and said OMG! You don't *never* use strlen() 
inside a loop! and the second version was writting:


file[FILE_SIZE] = ' ';
n = 0;
maxLength = 0;
while( n  FILE_SIZE )
{
while( file[n++] == ' ' ); wStart = n;
while( file[n++] != ' ' ); wLength = n - wStart;
if( wLength  maxLength )
{
  longestWordStart = wStart;
  maxLength = wLength;
}
}
strncpy( longestString , file + longestWordStart , maxLength );

This version takes 0.005 seconds.

I have no idea what kind of hardware this is running on - or even which 
compiler or OS.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Peter Lund
On Sat, 2007-12-15 at 11:59 -0800, Don Stewart wrote:
 firefly:
  What do you think the relative speeds are of the six small haskell
  programs at the end of this email?
  
  All they do is read from stdin and count the number of spaces they see.
  There are two that use strict bytestrings, two that use lazy
  bytestrings, and two that use the standard Haskell strings.  Three use a
  recursive function with an accumulator parameter and three use a foldl
  with a lambda function.
  
  Say the fastest one takes the time 1.  How much time will the others
  take?
  
  And how about memory?  How much memory do you think they require?  Let's
  say we feed a 150MB(*) file into each of them, how many megabytes do you
  think they end up using (as seen from the OS, not in terms of how big
  the live heap is)?
  
  I'm going to post full benchmarks + analysis on Wednesday.
 
 How are you compiling these programs, by the way?  ghc-6.8.2 -O2  ?
 (-O2 is required for bytestrings :)

With -O2.  I have measured with 6.8.1, 6.9.20071119, 6.9.20071208
(approx), and 6.9.200712xx (as of yesterday or today).  The picture
changes very little with the compiler, if it changes at all.

I have run them on three very different microarchitectures (2GHz
Athlon64 3000+, 1667MHz Core Duo, 600MHz Pentium III).

All the measurements are scripted.  'make phase1' compiles the
benchmarks, creates input files of various sizes, and runs each
benchmark once to gather information about memory use (peak RSS + ghc
RTS' own information about allocations and gcs), page faults, and an
strace.  This phase is not timing sensitive so I can browse the web and
listen to the music etc. while running it.

'make phase2' runs each benchmark a number of times, calculates the
average time for each + the relative size of the standard deviation +
how much user+sys is different from real (as reported by bash' built-in
time command).  A report with barcharts indicating relative time and
relative peak RSS is generated in either pure ASCII or in UTF-8 (with
fractional-width block chars so the charts look nice and have high
resolution).  If the measurements are deemed to be bad (too high
standard deviation or user+sys doesn't add up to real) then the barchart
is done with '%' characters.  The quality indicators for each timing
test are always printed out next to each bar, so we know how close we
are to being perfect or, conversely, how bad the measurements are.

There is a script that analyzes the I/O pattern and sums it up (as 4375
x read(3, 4096, ...) = 4096  followed by 1 x read(3, 4096, ...) = 1242
followed by 1 x read(3, 4096, ...) = 0 an similar).

There are a set of simple I/O programs in C so we can compare ghc's
performance with speed of light, and so different I/O strategies can
be compared in a cleaner, purer form.

There are also 'make cache' (runs cachegrind), 'make
hs/.doc' (creates a file with source code + core + stg + c-- +
assembly + times for a given benchmark), etc.

'make sysinfo' creates a file with information about the Linux
distribution used (/etc/lsb-release), kernel version (uname -a), CPU
(/proc/cpuinfo), and compilers used (ghc --version, gcc --version).

'make zipdata' creates a zip file of about 20K with all the raw time
measurements + the sysinfo.

I also have a set of scripts that installs each ghc version so 1) it is
easy for me to repeat the tests on various machines and 2) you can see
exactly which ghc versions I use and repeat the experiments yourself.

-Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] #haskell works

2007-12-15 Thread Bulat Ziganshin
Hello Andrew,

Sunday, December 16, 2007, 1:39:02 AM, you wrote:

 Takes 0.016 seconds to process a 2.4 MB file. [But not the same one Don
 used.]

 This version takes 0.005 seconds.

Don, it seems to be bound by memory speed rather than quality of generated
code. i suggest you to test it on fixed 32kb block processed many times

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[6]: [Haskell-cafe] #haskell works

2007-12-15 Thread Tim Chevalier
On 12/15/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 i see your point - it's easy to implement everything in GHC. probably
 its authors was sleeping last 15 years :)


As you well know, implementing things in GHC isn't always easy for
people who aren't named Simon, and people who are named Simon are
often busy not so much with sleeping as with coming up with things
that will lead to new papers rather than implementing straightforward
things that are already pointed out in existing papers :-) (I know
it's dangerous to call optimzations straightforward before you try
to implement them, but even so.)

 and ghc was so genuine that it was implemented general case without
 implementing special one :)


Isn't implementing the general case and leaving the users to use it to
implement the special ones what functional programming is about? :-)

  That's not true in C. The simplicity of Haskell (or rather,
  Core) means it's easy to implement a lot of things with a great deal
  of generality, an advantage that gcc doesn't have.

 Core language has the same complexity for generating good code as C, C-- or 
 LLVM


Sorry, I don't know what you mean here; I assume by complexity you
don't mean time complexity or space complexity, and anyway, I
don't know what those would mean as applied to a programming language.
Care to elaborate?

 you may believe in what you want. i prefer to say about real
 situation. if it will be possible to quickly write good Haskell
 compiler, it was be written many years ago


As others have pointed out, I think that's false. Resources, financial
and human, have been thrown at C compilation that have not been thrown
at Haskell compilers. As hard-working as the people who work on
Haskell compilers are, there aren't very many of them and none of them
have writing Haskell compilers as a job description.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
The blues isn't about feeling better, it's about making other people
feel worse, and making a few bucks while you're at it.  -- Bleeding
Gums Murphy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Yampa / AFRPVectorSpace.hs

2007-12-15 Thread Peter Verswyvelen
While studying the vector space class in AFRP, I encountered the following
strange code:

class Floating a = VectorSpace v a | v - a where
   ...
v1 ^-^ v2 = v1 ^+^ v1 -- (negateVector v2)


I have no idea why the (negateVector v2) has been commented out, but surely
this must be a typo?

Cheers,
Peter








___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cheap ByteString mmap

2007-12-15 Thread Don Stewart
A little mmap binding for ByteStrings.


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-mmap-0.1.1

Should be useful for managing file resources under pressure (cheaper
than a readFile, and with different constraints).

Posix only. the Win32 mmap for bytestrings is in the win32 package.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Roman Leshchinskiy

Andrew Coppin wrote:


Then Mr C++ looked at it and said OMG! You don't *never* use strlen() 
inside a loop! and the second version was writting:


file[FILE_SIZE] = ' ';
n = 0;
maxLength = 0;
while( n  FILE_SIZE )
{
while( file[n++] == ' ' ); wStart = n;
while( file[n++] != ' ' ); wLength = n - wStart;
if( wLength  maxLength )
{
  longestWordStart = wStart;
  maxLength = wLength;
}
}
strncpy( longestString , file + longestWordStart , maxLength );

This version takes 0.005 seconds.


Nice. I especially like the way it'll segfault if there is a blank at 
the end of the file.


Roman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Roman Leshchinskiy

Tim Chevalier wrote:


I think that's an awfully definite statement to make, given that C and
Haskell are very different languages, given how many high-level
optimizations are possible in Haskell that aren't in C, and given how
much higher programmer productivity is in Haskell than C. For example,
as above, loop unrolling turns out to be just a special case of
inlining. That's not true in C. The simplicity of Haskell (or rather,
Core) means it's easy to implement a lot of things with a great deal
of generality, an advantage that gcc doesn't have.


While this is true in general, loop optimisations are not a particularly 
good example, IMO. For them to be effective, you often have to consider 
things like instruction scheduling and register pressure which you can't 
really do on the Core level.


Roman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell works

2007-12-15 Thread Tim Chevalier
On 12/15/07, Roman Leshchinskiy [EMAIL PROTECTED] wrote:
 While this is true in general, loop optimisations are not a particularly
 good example, IMO. For them to be effective, you often have to consider
 things like instruction scheduling and register pressure which you can't
 really do on the Core level.

Fair enough for loop optimizations in general, but I think the point
about loop unrolling from the Secrets of the GHC Inliner paper that
I was referring to gives a counterexample to that. In imperative
languages, loop unrolling and inlining would be thought of as distinct
and very different optimizations -- in a pure functional language,
they can be unified. It seems to me that working in a pure functional
language makes it easy to write high-level optimizations that can be
specified very simply on a level like the level of Core that can then
be amplified by a smart backend that takes things like instruction
scheduling into account.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
Stupidity combined with arrogance and a huge ego will get you a long
way. -- Chris Lowe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Don Stewart
firefly:
 What do you think the relative speeds are of the six small haskell
 programs at the end of this email?
 
 All they do is read from stdin and count the number of spaces they see.
 There are two that use strict bytestrings, two that use lazy
 bytestrings, and two that use the standard Haskell strings.  Three use a
 recursive function with an accumulator parameter and three use a foldl
 with a lambda function.
 
 Say the fastest one takes the time 1.  How much time will the others
 take?
 
 And how about memory?  How much memory do you think they require?  Let's
 say we feed a 150MB(*) file into each of them, how many megabytes do you
 think they end up using (as seen from the OS, not in terms of how big
 the live heap is)?
 
 I'm going to post full benchmarks + analysis on Wednesday.
 
 -Peter
 
 *) hardddisk megabytes.  The file is 15034 bytes ≈ 143 mebibytes.
 
 
 PS: For extra credit, what do you think is the peak memory use for this
 program when given an input file of 150MB?

Well, I'm not going to wait till Wednesday for the numbers!

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.8.2

$ du -hs 150M 
150M



Program 1:

 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Lazy.Char8 as B
 import GHC.Int (Int64)
 
 -- note that D.BS.Lazy.Char8.length is ByteString - Int64
 --   D.BS.C8.length is ByteString - Int
 cnt:: B.ByteString - Int64
 cnt bs = B.length (B.filter (== ' ') bs)
 
 main = do s - B.getContents
  print (cnt s)

Ok, so lazy bytestrings. Should be constant space use, but two traversals
(since there's no lazy bytestring fusion, over each lazy chunk).  Not perfect,
but should be ok. length will consume chunks as they're produced by filter.

** Prediction:
Constant ~3M space use (runtime, plus small overhead)
Fast, due to chunk-wise processing.

** Result:
$ ghc -O2 A.hs -o A --make
$ time ./A  150M +RTS -sstderr
./A +RTS -sstderr  150M  1.01s user 0.10s system 98% cpu 1.123 total

And top says 40M allocated.

** Summary: Ok, pretty fast, but an unexpected(!) amount of memory allocated.

Now, this memory result is suspicious, I wonder if the now obsolete 'array 
fusion'
is messing things up. In Data.ByteString.Lazy, we have:

filter p = F.loopArr . F.loopL (F.filterEFL p) F.NoAcc

We keep meaning to replace this stuff with the stream fusion mechanisms, which 
compile a lot better. Perhaps the time has come to look at that :)

I'll put this memory allocation down as a bug that needs to be looked at.




Program 2:

 hs/space-bs-c8-acc-1.hs:
 {-# LANGUAGE BangPatterns #-}
 
 import qualified Data.ByteString.Char8 as B
 
 cnt:: Int - B.ByteString - Int
 cnt !acc bs = if B.null bs
then acc
else cnt (if B.head bs == ' ' then acc+1 else acc) (B.tail bs)
 
 main = do s - B.getContents
  print (cnt 0 s)

Strict bytestrings, and you manually fuse the length/filter calculation.
Allocating all that memory will cost you.

** Prediction:
O(N) memory, around 150M allocated
Slower, due to cache effects (more data to traverse) and more indirections.

** Result   
top says 154M
./B +RTS -sstderr  150M  1.10s user 0.52s system 111% cpu 1.454 total

** Summary: Seems reasonable, when its doing all that allocation. 



Program 2a:

But we could easily improve this program: Since:
length (filter (== ' ')
  ==
length (filterByte ' '
  ==
count ' '

And we have:

import qualified Data.ByteString.Char8 as B

cnt   :: B.ByteString - Int
cnt x = B.count ' ' x

main = do s - B.getContents
  print (cnt s)

** Prediction: Which should be a bit faster.

** Result:
$ time ./B  150M
24569024
./B  150M  0.66s user 0.55s system 113% cpu 1.070 total

** Summary: So that's the fastest program so far.

The rewrite rules to do these transformatoins used to be enabled, but 
need looking at again. There should also be no real benefit to manually fuse a
length . filter loop like this, however, the old fusion system used in
bytestring might have some small overhead here. This also needs looking at.


Program 2b:

We can do even better if we read the file in:

import qualified Data.ByteString.Char8as B
import System.IO.Posix.MMap

main = print . B.count ' ' = mmapFile 150M

** Prediction: super fast

** Result:

$ time ./B2
24569024
./B2  0.31s user 0.01s system 101% cpu 0.314 total

(similar results if you use vanilla B.readFile too, fwiw).

Summary: This suggests to me we could look again at how strings of unknown size
 are read in.




Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-15 Thread Yitzchak Gale
 Ah, good old seq. How I loathe it.
 Seriously, though, good catch. I always forget about seq when I'm doing
 stuff like this.

When using seq and _|_ in the context of categories,
keep in mind that Haskell composition (.)
is not really composition in the category-theoretic
sense, because it adds extra laziness. Use this
instead:

(.!) f g x = f `seq` g `seq` f (g x)

-Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Daniel Fischer
Am Sonntag, 16. Dezember 2007 04:07 schrieb Don Stewart:

 
 Program 7:

  ==
  hs/space-x-foldl.hs:
  {-# LANGUAGE BangPatterns #-}

  cnt   :: String - Int
  cnt bs= foldl (\sum c - if c == ' ' then sum+1 else sum) 0 bs

  main = do s - getContents
  print (cnt s)

 Hmm. Lazy accumulator eh, on String?  Should exhibit a space leak.

Doesn't (with -O2, at least), seems ghc's strictness analyser did a good job.
It is indeed about 10* slower than ByteStrings, but very memory friendly - 
and, actually on my machine it's faster (not much) than Data.List.foldl' .
And, again on my machine, Programme 3 is almost as slow when compiled with 
6.8.1 and twice as slow when compiled with 6.6.1.

 Nice little benchmark.

 -- Don

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Peter Lund
On Sun, 2007-12-16 at 04:53 +0100, Daniel Fischer wrote:

  Hmm. Lazy accumulator eh, on String?  Should exhibit a space leak.
 
 Doesn't (with -O2, at least), seems ghc's strictness analyser did a good job.
 It is indeed about 10* slower than ByteStrings, but very memory friendly - 

Daniel is right, there's no space leak.

Try it.  You'll get a nice surprise :)

-Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Don Stewart
firefly:
 On Sun, 2007-12-16 at 04:53 +0100, Daniel Fischer wrote:
 
   Hmm. Lazy accumulator eh, on String?  Should exhibit a space leak.
  
  Doesn't (with -O2, at least), seems ghc's strictness analyser did a good 
  job.
  It is indeed about 10* slower than ByteStrings, but very memory friendly - 
 
 Daniel is right, there's no space leak.
 
 Try it.  You'll get a nice surprise :)

Very nice. If we disable the strictness analsyer,

$ ghc -O2 -fno-strictness A.hs -no-recomp -o A

We get a core loop that looks like:

lgo :: Int - [Char] - Int
lgo n xs = case xs of
  [] - n
  a : as - lgo (case a of  -- sad dons
 C# c1_amH - case c1_amH of {
 ' '   - case n of I# i - I# (i +# 1)
 _- n;
 ) as


Look at that big lazy expression for 'n' not being forced!
And when run:

1015M 1017M onproc/1 - 0:05 22.36% A

Scary stuff.  Lots of Int thunks :)

 But enabling the strictness analyser:

lgo :: Int# - [Char] - Int#
lgo (n :: Int#) (xs :: [Char]) =
case xs of
  [] - n
  a : as - case a of 
C# c - case c of
  ' ' - lgo (n +# 1) as -- makes me happy
  _   - lgo nas

And life is good again :)

What is quite amazing is how efficient this program is.
I had to rerun this a dozen or so times, since I didn't quite believe it:

$ time ./A  /usr/obj/data/150M 
24569024
./A  /usr/obj/data/150M  2.42s user 0.47s system 100% cpu 2.883 total

Pretty stunning, I think.
Swapping in a slightly more eager structure, the lazy ByteString,

$ time ./A  /usr/obj/data/150M
24569024
./A  /usr/obj/data/150M  0.86s user 0.07s system 98% cpu 0.942 total

improves things by a good amount, but I think we can revisit the low level
performance of lazy bytestrings again, in light of all the changes to the
optimiser in the past 2 years.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Peter Lund
On Sat, 2007-12-15 at 21:18 -0800, Don Stewart wrote:

 What is quite amazing is how efficient this program is.

Yep.  I was very surprised too.

Turns out there *was* a reason to run those string benchmarks, eh? ;)

 improves things by a good amount, but I think we can revisit the low level
 performance of lazy bytestrings again, in light of all the changes to the
 optimiser in the past 2 years.

Yep.

-Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-15 Thread Peter Lund
On Sat, 2007-12-15 at 19:07 -0800, Don Stewart wrote:

 Well, I'm not going to wait till Wednesday for the numbers!

But I got you to write down predictions before you ran the tests, which
is precisely what I wanted :)

 Summary,
 
   * Program 1 is fast, as expected, but exhbits a bug in the bytestring
 library's lazy bytestring fusion system.  Something in length or 
 filter
 isn't doing the right job. This code will be replaced by the stream 
 fusion
 system soon.

Good.

   * Program 2: as expected. strict IO uses O(N) space, and that has 
 performance 
 effects.
 
   * Program 3: lazy bytestrings use constant space, but you better avoid
 redundant bounds checks in the inner loops. 

Maybe its extra bounds-checking that makes it slow, as you say.  It
probably is.  I must admit that I couldn't follow the
core/stg/C--/assembly code at all.

   * Program 4: strings are silly

No they are not.

They are the default data structure for text and give the baseline that
bytestrings should beat.

I find it interesting to see *if* bytestrings beat it and if so, by how
much.  The vanilla string versions of my tests all use less memory than
any of the other versions, but they are a bit slower.  And perhaps not
as much slower as they should be...

   * Program 5: as expected. similar to program 2.
 
   * Program 6: strict foldl's over lazy bytestrings are good :)
fast, and constant space.
 
   * Program 7: see program 4.
 
 Pretty much as expected then, but with a bug identified in lazy bytestring 
 fusion (I think).
 
 Nice little benchmark.

Thanks :)

There are more...

-Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe