[commit: nofib] master: spectral: fix secretary (313812d)

git at git.haskell.org git at git.haskell.org
Mon Mar 13 23:44:47 UTC 2017


Repository : ssh://git@git.haskell.org/nofib

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/313812d319e009d698bc1a4d2e8ac26d4dfe3c0a/nofib

>---------------------------------------------------------------

commit 313812d319e009d698bc1a4d2e8ac26d4dfe3c0a
Author: Michal Terepeta <michal.terepeta at gmail.com>
Date:   Mon Mar 13 18:35:46 2017 -0400

    spectral: fix secretary
    
    This should fix the benchmark by:
    - Not importing `IOExts`.
    - Using `randomRs` with a predictable seed instead of `randomRIOs` to
      make the runs reproducible (the latter is using global RNG).
    - Bumping one of the parameter to make it run for a bit longer (2s
      instead of 0.4s).
    
    Signed-off-by: Michal Terepeta <michal.terepeta at gmail.com>
    
    Test Plan: build & run
    
    Reviewers: bgamari
    
    Differential Revision: https://phabricator.haskell.org/D3328


>---------------------------------------------------------------

313812d319e009d698bc1a4d2e8ac26d4dfe3c0a
 spectral/Makefile                   |  4 ++--
 spectral/secretary/Main.lhs         | 30 ++++++++++--------------------
 spectral/secretary/Makefile         |  2 +-
 spectral/secretary/secretary.stdout |  2 +-
 4 files changed, 14 insertions(+), 24 deletions(-)

diff --git a/spectral/Makefile b/spectral/Makefile
index e60718d..c66d3bd 100644
--- a/spectral/Makefile
+++ b/spectral/Makefile
@@ -5,10 +5,10 @@ SUBDIRS = ansi atom awards banner boyer boyer2 calendar cichelli circsim \
           clausify constraints cryptarithm1 cryptarithm2 cse eliza expert \
           fft2 fibheaps fish gcd hartel integer knights lambda last-piece lcss life \
 	  mandel mandel2 mate minimax multiplier para power pretty primetest \
-	  puzzle rewrite scc simple sorting sphere treejoin
+	  puzzle rewrite scc secretary simple sorting sphere treejoin
 
 # compreals	no suitable test data
-OTHER_SUBDIRS = compreals lambda last-piece secretary triangle
+OTHER_SUBDIRS = compreals lambda last-piece triangle
 
 include $(TOP)/mk/target.mk
 
diff --git a/spectral/secretary/Main.lhs b/spectral/secretary/Main.lhs
index f922caa..03ac1f5 100644
--- a/spectral/secretary/Main.lhs
+++ b/spectral/secretary/Main.lhs
@@ -16,27 +16,19 @@ import System.Random
 import Data.List
 import System.IO
 import Control.Monad
-import IOExts
 
 type Process = [Integer] -> Bool
 
--- added by SimonM
-randomRIOs :: Random a => (a,a) -> IO [a]
-randomRIOs rng 
-  = do rs <- unsafeInterleaveIO (randomRIOs rng)
-       r  <- randomRIO rng
-       return (r:rs)
-
--- modified for Haskell 98 by SimonM
-simulate :: Int -> Integer -> Process -> IO Double
-simulate n m proc =
-  do tries <- sequence [ fmap proc (randomRIOs (1,m)) | _ <- [1..n] ]
-     return (length (filter id tries) // n)
- where
-  n // m = fromInt n / fromInt m
+-- Modified for Haskell 98 by SimonM
+-- (2017-03): Modified by michalt to fix build and avoid global RNG
+simulate :: Int -> Integer -> Process -> Double
+simulate n m proc = length (filter id tries) // n
+  where
+    tries = [ proc (randomRs (1,m) (mkStdGen seed)) | seed <- [1..n] ]
+    n // m = fromIntegral n / fromIntegral m
 
-sim :: Int -> IO Double
-sim k = simulate 1000 100 proc
+sim :: Int -> Double
+sim k = simulate 5000 100 proc
  where
   proc rs = [best] == take 1 afterk
    where
@@ -46,9 +38,7 @@ sim k = simulate 1000 100 proc
     afterk = dropWhile (< bestk) (drop k xs)
 
 main :: IO ()
-main =
-  do ps <- sequence [ sim k | k <- [35..39] ]
-     print ps
+main = print [ sim k | k <- [35..39] ]
 \end{code}
 
 When I run this module with ghc-4.01, I get _wrong_ results, and a bus
diff --git a/spectral/secretary/Makefile b/spectral/secretary/Makefile
index 86edad6..ad87e31 100644
--- a/spectral/secretary/Makefile
+++ b/spectral/secretary/Makefile
@@ -1,5 +1,5 @@
 TOP = ../..
 include $(TOP)/mk/boilerplate.mk
 -include opts.mk
-SRC_HC_OPTS += -fglasgow-exts
+SRC_HC_OPTS += -package random
 include $(TOP)/mk/target.mk
diff --git a/spectral/secretary/secretary.stdout b/spectral/secretary/secretary.stdout
index e279cd0..64eae4b 100644
--- a/spectral/secretary/secretary.stdout
+++ b/spectral/secretary/secretary.stdout
@@ -1 +1 @@
-[0.368,0.386,0.357,0.38,0.392]
+[0.356,0.356,0.358,0.3596,0.3594]



More information about the ghc-commits mailing list