
Sebastian Sylvan wrote:
On 1/4/06, Josh Goldfoot
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.