{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE ScopedTypeVariables #-} -- | Benchmark the folding functions. As these functions need several tables to -- read data from, we have to initialize some stuff. The benchmarks test access -- and calculation patterns that are common in bioinformatics. -- -- For best results, compile with "-Odph -fllvm" (6.13) or "-Odph" (6.12). This -- is for the unboxed vectors. Both benchmarks should clock at about 10us. module Main where import Criterion.Main import Control.DeepSeq import System.Random import qualified Data.Vector.Unboxed as VU import Data.PrimitiveArray import Data.PrimitiveArray.Ix import Data.Primitive.Types hi = 999 main = do rng <- getStdGen let (table :: PrimArray (Int,Int) Int) = fromAssocs (0,0) (hi,hi) 0 $ zip [ (i,j) | i<-[0..hi] , j<-[0..hi] ] $ randomRs (0,hi) rng print $ table ! (0,0) print $ table ! (hi,hi) defaultMain [ bgroup "compare" [ bench "unsafeIndex" $ whnf (\k -> {-# CORE "sum/unsafeIndex" #-} VU.foldl' min 999999 $ VU.map (\ij -> table ! ij) $ VU.generate k (\z -> (z,z)) ) hi , bench "twiceIndex" $ whnf (\k -> {-# CORE "sum/twiceIndex" #-} VU.foldl' min 999999 $ VU.map (\(i,j) -> (table ! (i,0)) + (table ! (0,j))) $ VU.generate k (\z -> (z,z)) ) hi ] ]