Help optimize fannkuch program

Well, playing with Haskell I have literally trasnlated my c++ program http://shootout.alioth.debian.org/u64q/program.php?test=fannkuchredux&lang=gpp&id=3and got decent performance but not that good in comparisonwith c++ On my machine Haskell runs 52 secs while c++ 30 secs.(There is Haskell entry that is fastest but unfortunately does not runs on test machine is on par with c++http://shootout.alioth.debian.org/u64q/program.php?test=fannkuchredux&lang=ghc&id=3)There is something which I have missing since programsare identical.Aa with previous entries you gurus here helped a lot in both helpand learning experience.I simply love Haskell ;)I plan to contribute this program as it is much faster than current runningentry http://shootout.alioth.debian.org/u64q/program.php?test=fannkuchredux&lang=ghc&id=2even if it is multithreaded and my is not. This is program: {-# LANGUAGE CPP, BangPatterns #-}{- The Computer Language Benchmarks Game http://shootout.alioth.debian.org/ contributed by Branimir Maksimovic -} import System.Environmentimport Text.Printfimport Data.Bits import qualified Data.Vector.Unboxed.Mutable as VMimport qualified Data.Vector.Generic.Mutable as VGimport qualified Data.Vector.Unboxed as V main = do n <- getArgs >>= readIO.head (checksum,maxflips) <- fannkuch n printf "%d\nPfannkuchen(%d) = %d\n" checksum n maxflips fannkuch n = do !perm <- V.unsafeThaw $ V.fromList [1..n] !tperm <- VG.new n !cnt <- VG.replicate n 0 let loop :: Int -> Int -> Int -> IO(Int,Int) loop !c !m !pc = do !b <- next_permutation perm n cnt if b == False then return (c,m) else do VM.unsafeCopy tperm perm !flips <- count_flips tperm 0 loop (c + (if pc .&. 1 == 0 then flips else -flips)) (max m flips) (pc+1) r <- loop 0 0 1 return r next_permutation :: VM.IOVector Int -> Int -> VM.IOVector Int-> IO(Bool)next_permutation !perm !n !cnt = do !i <- loop 1 if(i >= n) then return False else do !v <- VM.unsafeRead cnt i VM.unsafeWrite cnt i (v+1) return True where loop :: Int -> IO(Int) loop !i | i < n = do !tmp <- VM.unsafeRead perm 0 let rotate :: Int -> IO() rotate !j = if j >= i then do VM.unsafeWrite perm i tmp return () else do !v <- VM.unsafeRead perm (j+1) VM.unsafeWrite perm j v rotate (j+1) rotate 0 !v <- VM.unsafeRead cnt i if v >= i then do VM.unsafeWrite cnt i 0 loop (i+1) else return i | otherwise = return i count_flips :: VM.IOVector Int -> Int -> IO(Int)count_flips !tperm !flips = do !f <- VM.unsafeRead tperm 0 if f == 1 then return flips else do VG.reverse $ VM.unsafeSlice 0 f tperm count_flips tperm (flips+1)

On Sun, Dec 2, 2012 at 3:12 PM, Branimir Maksimovic
Well, playing with Haskell I have literally trasnlated my c++ program
http://shootout.alioth.debian.org/u64q/program.php?test=fannkuchredux&lang=gpp&id=3 and got decent performance but not that good in comparison with c++ On my machine Haskell runs 52 secs while c++ 30 secs.
Did you compile with -O2 -fllvm? On my machine: C++ 28 sec Mine -O2 -fllvm 37 sec Yours -O2 -fllvm 41 sec Mine -O2 48 sec Yours -O2 54 sec My version of your Haskell code is here: http://hpaste.org/78705

Thanks. Your version is much faster.Yes, I have compiled with ghc --make -O2 -fllvm -optlo-O3 -optlo-constprop fannkuchredux4.hs(there is bug in ghc 7.4.2 regarding llvm 3.1 > which is circumvented with constrprop)
results: yours:bmaxa@maxa:~/shootout/fannkuchredux$ time ./fannkuchredux4 123968050Pfannkuchen(12) = 65
real 0m39.200suser 0m39.132ssys 0m0.044s
mine:bmaxa@maxa:~/shootout/fannkuchredux$ time ./fannkuchredux 123968050Pfannkuchen(12) = 65
real 0m50.784suser 0m50.660ssys 0m0.092s
Seems that you machine is faster than mine and somewhat better for executing mine version.Thanks ! Should I contribute your version on shootout site?
Date: Mon, 3 Dec 2012 00:01:32 -0800
Subject: Re: [Haskell-cafe] Help optimize fannkuch program
From: bos@serpentine.com
To: bmaxa@hotmail.com
CC: haskell-cafe@haskell.org
On Sun, Dec 2, 2012 at 3:12 PM, Branimir Maksimovic

Here it is :http://shootout.alioth.debian.org/u64/program.php?test=fannkuchredux&lang=ghc&id=4
Date: Mon, 3 Dec 2012 15:32:20 -0800
Subject: Re: [Haskell-cafe] Help optimize fannkuch program
From: bos@serpentine.com
To: bmaxa@hotmail.com
CC: haskell-cafe@haskell.org
On Mon, Dec 3, 2012 at 11:18 AM, Branimir Maksimovic
participants (2)
-
Branimir Maksimovic
-
Bryan O'Sullivan