[Haskell-cafe] Help optimize fannkuch program

Branimir Maksimovic bmaxa at hotmail.com
Mon Dec 3 00:12:12 CET 2012


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)


 		 	   		  
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121202/c7a30d9b/attachment.htm>


More information about the Haskell-Cafe mailing list