Skip to content

Instantly share code, notes, and snippets.

@spockz
Created September 11, 2010 09:48
Show Gist options
  • Save spockz/575041 to your computer and use it in GitHub Desktop.
Save spockz/575041 to your computer and use it in GitHub Desktop.
module Main where
import Criterion
import Control.Concurrent.CHP.Monad
import Data.IORef
import qualified Data.Map as M
import Progression.Main
import Random
import System.IO.Unsafe
runAll = defaultMain . bgroup "" . map (\c@(a,b) -> bench a ( b))
main = runAll [("SimpleCalc", Main.run)
,("SimpleCalc Memoised1", Main.runm)
]
run :: IO ()
run = genList >>= (putStrLn . show . map calc)
runm :: IO ()
runm = do xs <- genList
store <- newIORef M.empty
(putStrLn.show) $ map (calcM store) xs
-- | Yes, I'm very sorry about the unsafePerformIO here. And no, my name is not
-- Simon unfortunately. :)
calcM :: IORef (M.Map Int Integer) -> Int -> Integer
calcM storevar a = unsafePerformIO $
do store <- readIORef storevar
maybe (do let result = calc a
writeIORef storevar (M.insert a result store)
return result
)
return
(M.lookup a store)
calc :: Int -> Integer
calc = fib
genList :: IO [Int]
genList = do g <- newStdGen
return $ take 10000 $ randomRs (1,25) g
fib :: Int -> Integer
fib n
| n == 0 = 0
| n == 1 = 1
| n > 1 = fib (n-1) + fib (n-2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment