Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-05 Thread Chris Kuklewicz
I piped the output of fasta (with N=250,000) into the entries on the
wiki [2] which I compiled with 'ghc -O2'.  Watching with 'top', I saw
over 400MB of RSIZE by the end.  So perhaps I am benchmarking wrong,
since this is the same memory usage as the original reverse-compliment
entry, and roughly the same speed.


Donald Bruce Stewart wrote:
 I've added an entry on the hawiki[1] for the regex-dna benchmark, and
 posted a smaller (down to 15 lines), faster entry for
 [2]reverse-complement, using string indexing from Alex.
 
 Cheers, 
   Don
 
 [1] http://haskell.org/hawiki/ShootoutEntry
 [2] http://haskell.org/hawiki/ReverseComplementEntry
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-04 Thread Sebastian Sylvan
On 1/4/06, Josh Goldfoot [EMAIL PROTECTED] wrote:
 Keep in mind that the shootout requires that the first 30 permutations 
 printed out by the Fannkuch benchmark to be exactly those given in the 
 example.

Well I'm one step closer to just not caring about the shootout anymore.

The spec says *nothing* about the order of permutation. So the fact
that they require them to be generated in a specific order (I'm sure
it's just coincidence that it's the order you get in thet typical
C-style permutation generator) is silly.

What's the point of a language benchmark if all it tests is your
language's ability to instruction-for-instruction implement a C
algorithm? It's certainly possible to implement the exact same
algorithm using Ptr Word8 etc, but what's the point? It's not
idiomatic Haskell anymore and as such has little or no interest to me.

This is silly!

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-04 Thread Chris Kuklewicz
Sebastian Sylvan wrote:
 On 1/4/06, Josh Goldfoot [EMAIL PROTECTED] wrote:
 
Keep in mind that the shootout requires that the first 30 permutations 
printed out by the Fannkuch benchmark to be exactly those given in the 
example.
 
 
 Well I'm one step closer to just not caring about the shootout anymore.
 
 The spec says *nothing* about the order of permutation. So the fact
 that they require them to be generated in a specific order (I'm sure
 it's just coincidence that it's the order you get in thet typical
 C-style permutation generator) is silly.
 
 What's the point of a language benchmark if all it tests is your
 language's ability to instruction-for-instruction implement a C
 algorithm? It's certainly possible to implement the exact same
 algorithm using Ptr Word8 etc, but what's the point? It's not
 idiomatic Haskell anymore and as such has little or no interest to me.
 
 This is silly!
 
 /S

It is silly.  But real work almost always involves having to heed
requirements that are annoying.  And for a benchmark, it helps to keep
everyone using a similar algorithm.  That said, this is the code Bertram
Felgenhauer posted to create the right permutation sequence:

 import System (getArgs)
 import Data.List (foldl')
 

 rotate n (x:xs) = rot' n xs where
 rot' 1 xs = x:xs
 rot' n (x:xs) = x:rot' (n-1) xs
 
 permutations :: [Int] - [[Int]]
 permutations l = foldr perm' [l] [2..length l] where
 perm' n l = l = take n . iterate (rotate n)
 

This is idiomatic Haskell to my eyes.  No simulated c-style loops, no
arrays, no Ptr.

The rest of the code is

 flop :: Int - [Int] - [Int]
 flop n xs = rs
   where (rs, ys) = fl n xs ys
 fl 0 xs ys = (ys, xs)
 fl n (x:xs) ys = fl (n-1) xs (x:ys)
 
 steps :: Int - [Int] - Int
 steps n (1:_)= n
 steps n ts@(t:_) = (steps $! (n+1)) (flop t ts)
 
 main = do
 args - getArgs
 let arg = if null args then 7 else read $ head args
 mapM_ (putStrLn . concatMap show) $ take 30 $ permutations [1..arg]
 putStr $ Pfannkuchen( ++ show arg ++ ) = 
 putStrLn $ show $ foldl' (flip (max . steps 0)) 0 $ permutations [1..arg]

Where flop using fl, which is something that cannot even be expressed
without lazy evaluation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-04 Thread Bulat Ziganshin
Hello Josh,

Wednesday, January 04, 2006, 6:00:16 AM, you wrote:

JG I was able to significantly speed up the code by replacing the flip 
function with a function that relies entirely on pattern matching (no splitAts 
or reverses).  It looks ugly, though:

JG mangle list@(1:xs) = list
JG mangle (2:x2:xs) = x2:2:xs
JG mangle (3:x2:x3:xs) = x3:x2:3:xs
JG ... and so on.

such code can be generated by Template Haskell. anyway, one of
purposes of TH creation was to add user-defined optimizations to the
language


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-04 Thread Sebastian Sylvan
On 1/4/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  On 1/4/06, Josh Goldfoot [EMAIL PROTECTED] wrote:
 
 Keep in mind that the shootout requires that the first 30 permutations 
 printed out by the Fannkuch benchmark to be exactly those given in the 
 example.
 
 
  Well I'm one step closer to just not caring about the shootout anymore.
 
  The spec says *nothing* about the order of permutation. So the fact
  that they require them to be generated in a specific order (I'm sure
  it's just coincidence that it's the order you get in thet typical
  C-style permutation generator) is silly.
 
  What's the point of a language benchmark if all it tests is your
  language's ability to instruction-for-instruction implement a C
  algorithm? It's certainly possible to implement the exact same
  algorithm using Ptr Word8 etc, but what's the point? It's not
  idiomatic Haskell anymore and as such has little or no interest to me.
 
  This is silly!
 
  /S

 It is silly.  But real work almost always involves having to heed
 requirements that are annoying.  And for a benchmark, it helps to keep
 everyone using a similar algorithm.  That said, this is the code Bertram
 Felgenhauer posted to create the right permutation sequence:


In this case the benchmark was about indexing small sequences of
numbers, not about generating a specific sequence of permutations, so
it would've been better, IMO, to just let people use whatever
permutation algorithm they prefer.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-04 Thread Sebastian Sylvan
On 1/4/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  On 1/4/06, Josh Goldfoot [EMAIL PROTECTED] wrote:
 
 Keep in mind that the shootout requires that the first 30 permutations 
 printed out by the Fannkuch benchmark to be exactly those given in the 
 example.
 
 
  Well I'm one step closer to just not caring about the shootout anymore.
 
  The spec says *nothing* about the order of permutation. So the fact
  that they require them to be generated in a specific order (I'm sure
  it's just coincidence that it's the order you get in thet typical
  C-style permutation generator) is silly.
 
  What's the point of a language benchmark if all it tests is your
  language's ability to instruction-for-instruction implement a C
  algorithm? It's certainly possible to implement the exact same
  algorithm using Ptr Word8 etc, but what's the point? It's not
  idiomatic Haskell anymore and as such has little or no interest to me.
 
  This is silly!
 
  /S

 It is silly.  But real work almost always involves having to heed
 requirements that are annoying.  And for a benchmark, it helps to keep
 everyone using a similar algorithm.  That said, this is the code Bertram
 Felgenhauer posted to create the right permutation sequence:

  import System (getArgs)
  import Data.List (foldl')
 
 
  rotate n (x:xs) = rot' n xs where
  rot' 1 xs = x:xs
  rot' n (x:xs) = x:rot' (n-1) xs
 
  permutations :: [Int] - [[Int]]
  permutations l = foldr perm' [l] [2..length l] where
  perm' n l = l = take n . iterate (rotate n)
 

 This is idiomatic Haskell to my eyes.  No simulated c-style loops, no
 arrays, no Ptr.

But it certainly isn't very readable compared to the other
permutations algorithms we've seen.
I consider a major goal in writing code, especially code that's to be
compared against other languages, in a way so that people won't have
to struggle to understand it. If it takes a few more lines to do, then
so be it.

It takes me several minutes to parse that algorithm and understand
what it does, while the other permutation algorithms are obvious
within seconds.
Imagine how a C programmer would feel when reading it!

So again, it would be better if the shootout allowed all the languages
to generate the input in any way they wanted, and concentrate on
locking down the specifics of the *algorithm* (in this case reversing
a large number of short sub-sequences), that way other languages won't
have to resort to ugly solutions just to match the version written in
C.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Progress on shootout entries

2006-01-03 Thread Kimberley Burchett
I took a quick crack at optimizing fannkuch.hs.  I got it down from 33s to 
1.25s on my machine, with N=9.  That should put it between forth and 
ocaml(bytecode) in the shootout page.  The main changes I made were using 
Int instead of Int8, foldl' to accumulate the max number of folds, a 
custom flop function rather than a combination of reverse and splitAt, and 
a simpler definition for permutations.


   http://kimbly.com/code/fannkuch.hs

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


[Haskell-cafe] Re: Progress on shootout entries

2006-01-03 Thread Josh Goldfoot
Keep in mind that the shootout requires that the first 30 permutations printed 
out by the Fannkuch benchmark to be exactly those given in the example.  Any 
other order of permutations gets your code labeled Error by the shootout 
administrators.  See the discussion here:

http://alioth.debian.org/tracker/index.php?func=detailaid=302527group_id=30402atid=411646

The version of Fannkuch on the site before I got there used a permutation 
function that did not comply with this requirement.  My only contribution was 
to translate the acceptable algorithm into Haskell.  (The inefficient flop 
stuff and the other errors were not my fault, I swear!)  The resulting (slow) 
code can definitely be sped up, but unfortunately the shootout benchmark favors 
imperative languages (and impure functional languages, I guess).

I suppose we could have two permutation-generating functions:  One used only to 
generate the first 30 required by the benchmark, and another that is actually 
used to calculate the fannkuch value.  It's not clear how the shootout 
rule-lawyers would look that.  It seems to violate the same way rule.

I was able to significantly speed up the code by replacing the flip function 
with a function that relies entirely on pattern matching (no splitAts or 
reverses).  It looks ugly, though:

mangle list@(1:xs) = list
mangle (2:x2:xs) = x2:2:xs
mangle (3:x2:x3:xs) = x3:x2:3:xs
... and so on.


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


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-03 Thread Jan-Willem Maessen

I was surprised to learn that indexed insertion:

permutations (x:xs) =
[insertAt n x perms | perms - permutations xs,
  n - [0..length xs] ]

insertAt :: Int - a - [a] - [a]
insertAt 0 y xs = y:xs
insertAt n y (x:xs) = x:(insertAt (n-1) y xs)

was faster than the usual version of permutation based on inserts:

permutations (x:xs) =
[insertAt n x perms | perms - permutations xs,
  n - [0..length xs] ]
insertAt 0 y xs = y:xs
insertAt n y (x:xs) = x:(insertAt (n-1) y xs)

However, try these on for size.  The non-strict flop, which  
traverses its input exactly once, is the most surprising and made by  
far the biggest difference:



findmax :: [[Int]] - Int
findmax xss = fm xss 0
  where fm [] mx = mx
fm (p:ps) mx = fm ps $! (countFlops p `max` mx)

countFlops :: [Int] - Int
countFlops as = cf as 0
  where cf(1:_) flops = flops
cf xs@(x:_) flops = cf (flop x xs) $! (flops+1)

flop :: Int - [Int] - [Int]
flop n xs = rs
  where (rs,ys) = fl n xs ys
fl 0 xs ys = (ys, xs)
fl n (x:xs) ys = fl (n-1) xs (x:ys)


On Jan 3, 2006, at 8:01 PM, Kimberley Burchett wrote:

I took a quick crack at optimizing fannkuch.hs.  I got it down from  
33s to 1.25s on my machine, with N=9.  That should put it between  
forth and ocaml(bytecode) in the shootout page.  The main changes I  
made were using Int instead of Int8, foldl' to accumulate the max  
number of folds, a custom flop function rather than a combination  
of reverse and splitAt, and a simpler definition for permutations.


   http://kimbly.com/code/fannkuch.hs

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


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