[Haskell-cafe] The Computer Language Benchmarks Game: pidigits

Arnaud Payement arnaud.payement at gmail.com
Thu May 21 15:15:16 EDT 2009


Hi all, 

I recently decided to rewrite the pidigits benchmark of the debian shootout (shootout.alioth.debian.org) as toy project.
However, it seems that on my machine, the code seems to be more performant than both the current entry and the proposed replacement (see http://www.haskell.org/haskellwiki/Shootout/Pidigits) for the same number of lines. 
Do you think it might be worth submitting my entry? Here is my code,:

{-# OPTIONS -O2 -optc-O3 #-}
--
-- The Great Computer Language Shootout
-- http://shootout.alioth.debian.org/
-- by Arnaud Payement
--

import System

data F = F Integer Integer Integer Integer

extract s@(F k n a d) = ((n*3+a) `div` d, (n*4+a) `div` d, s)

update (F k n a d) = F (k+1) (n*k) ((a+n*2)*y) (d*y) where y = 2*k+1

next state = let (u, v, s'@(F k n a d)) = extract (update state) in
  if (n > a || (u /= v)) then next s' else (show u, F k (n*10) ((a-d*u)*10) d)
  
digits = ("", (F 1 1 0 1)):[next state | state <- map snd digits]

pr (d:t) k n | k > n = putStr ""
             | k `mod` 10 /= 0 = putStr d >> pr t (k+1) n
             | otherwise = putStrLn (d ++ "\t:" ++ show k) >> pr t (k+1) n

main = pr (map fst (tail digits)) 1 . read . head =<< getArgs

Best,
Arnaud

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090521/7ccabe9c/attachment.html


More information about the Haskell-Cafe mailing list