Shootout/Harmonic
A Shootout Entry for the harmonic benchmark. Each program should calculate the partial sum of the Harmonic series using the same naïve double-precision algorithm.
Correct output N = 10,000,000 is:
16.695311366
Timing[edit]
Timing on Linux Debian/x86, gcc 3.3.4, ghc 6.4.1.
||Entry || Time in seconds (n=100000000) || LOC || Compile flags || ||Old || 3.44 || 8 || -O2 -optc-O3 -optc-ffast-math || ||Current || 2.76 || 8 || -fglasgow-exts -O2 -optc-O3 -optc-ffast-math || ||Unboxed || 2.033 || 3 || -O2 -fasm -fglasgow-exts || ||Proposed || 2.033 || 3 || -O2 -fasm ||
Proposed entry[edit]
More beautiful than the unboxed entry, identical code generated. Short too. Compile with -O2 -fasm -fglasgow-exts
--
-- The Great Computer Language Shootout
-- http://shootout.alioth.debian.org/
-- sum harmonic series
--
-- Contributed by Greg Buchholz
-- Enhanced by Einar Karttunen, Mirko Rahn, Bertram Felgenhauer and Don Stewart
--
import System; import Numeric
main = putStrLn . (\n -> showFFloat (Just 9) (loop n 0) []) . read . head =<< getArgs
loop d s = if d == 0 then s :: Double else loop (d-1 :: Int) (s + 1/fromIntegral d)
Unboxed entry[edit]
{-# OPTIONS -O2 -fasm -fglasgow-exts #-}
--
-- The Great Computer Language Shootout
-- http://shootout.alioth.debian.org/
-- sum harmonic series
--
-- Compile with: ghc -fexcess-precision -o Harm Harm.hs
--
-- Contributed by Greg Buchholz
-- Enhanced by Einar Karttunen, Mirko Rahn and Don Stewart
--
import System; import Numeric; import GHC.Base; import GHC.Float
main = putStrLn . (\(I# n) -> showFFloat (Just 9) (D# (loop n 0.0##)) []) . read . head =<< getArgs
loop d s = if d ==# 0# then s else loop (d-#1#) (s +## (1.0## /## int2Double# d))
Old entry[edit]
Unbox the loop in the original entry, and crank up gcc.
I don't get a speed difference between the two versions with GHC-6.4.1 and gcc-4.0.3 on Debian/x86. ~Lemmih
In response: On OpenBSD/x86 it's more than twice as fast. However, the speedup is much less on Linux/x86 with the same gcc (3.3.5). On Linux, for N=1000000000, I have the old version as 1.2x slower than the unboxed version. On OpenBSD the old version is 2.8x slower. -- Don
{-# OPTIONS -fglasgow-exts -O2 -optc-O3 #-}
import System
import Numeric
import GHC.Base
import GHC.Float
main = do (I# n) <- getArgs >>= return . read . head
putStrLn $ showFFloat (Just 9) (D# (loop n 0.0##)) []
loop 0# s = s
loop d s = loop (d-#1#) (s +## (1.0## /## int2Double# d))
The original entry[edit]
-- The Great Computer Language Shootout
-- http://shootout.alioth.debian.org/
-- sum harmonic series
-- compile with: ghc -O2 -o Harm Harm.hs
-- contributed by Greg Buchholz
-- enhanced by Einar Karttunen
-- further enhanced by Mirko Rahn (n additions less)
import System(getArgs)
import Numeric(showFFloat)
main :: IO ()
main = getArgs >>= \ (~n:_) ->
putStrLn $ showFFloat (Just 9) (loop (read n) 0) []
loop :: Double -> Double -> Double
loop 0 s = s
loop d s = loop (d-1) (s+(1/d))