Shootout/Random
< Shootout
Jump to navigation
Jump to search
A Shootout Entry for the random benchmark.
Current entry
Using `rem` (as the Clean entry does) halves running time on Linux/p4 (!) and about 10% faster on OpenBSD.
I see the same effect, or greater (!), on my powerbook with those compile options. Are you gong to submit this? -- ChrisKuklewicz
This has been submitted, however only a minor speedup occured on the gp4 test machine. Sigh. -- Dons
-- $Id: random-ghc.code,v 1.28 2006/01/08 23:33:35 igouy-guest Exp $
-- http://shootout.alioth.debian.org
--
-- Original by Simon Marlow
-- Heavily modified by Einar Karttunen, further by Don Stewart
--
-- ghc -o c C.hs -O3 -optc-O3 -fexcess-precision -fglasgow-exts
--
import System; import Numeric
main = putStrLn . (\n -> showFFloat (Just 9) (randl (n-1) 42) []) . read . head =<< getArgs
randl (n::Int) (seed::Int) = if n == 0 then nr else randl (n-1) ns :: Double
where (ns,nr) = ((seed * ia + ic) `rem` im, 100 * (fromIntegral ns) / fromIntegral im)
(im,ia,ic) = (139968,3877,29573)
Current entry
Shortest entry in any language
{-# OPTIONS -fglasgow-exts -O2 -optc-O3 #-}
-- $Id: random-ghc.code,v 1.28 2006/01/08 23:33:35 igouy-guest Exp $
-- http://shootout.alioth.debian.org
--
-- Original by Simon Marlow
-- Heavily modified by Einar Karttunen and Don Stewart
import System; import Numeric
main = putStrLn . (\n -> showFFloat (Just 9) (randl (n-1) 42) []) . read . head =<< getArgs
randl (n::Int) (seed::Int) = if n == 0 then nr else randl (n-1) ns :: Double
where (ns,nr) = ((seed * ia + ic) `mod` im, (fromIntegral ns) * (100 / fromIntegral im))
(im,ia,ic) = (139968,3877,29573)
Older entry
{-# OPTIONS -O3 #-}
-- $Id: random-ghc.code,v 1.28 2006/01/08 23:33:35 igouy-guest Exp $
-- http://shootout.alioth.debian.org
--
-- Original by Simon Marlow
-- Heavily modified by Einar Karttunen
import System(getArgs)
import Numeric(showFFloat)
main = do ~[n] <- getArgs
putStrLn (showFFloat (Just 9) (randl 100 ((read n)-1) 42) "")
randl :: Double -> Int -> Int -> Double
randl max n seed = newseed `seq` newrand `seq`
if n == 0 then newrand else randl max (n-1) newseed
where newseed = (seed * ia + ic) `mod` im
newrand = (fromIntegral newseed) * (max / fromIntegral im)
im = 139968
ia = 3877
ic = 29573