File: Bench.hs

package info (click to toggle)
haskell-chimera 0.3.4.0-1
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 140 kB
  • sloc: haskell: 829; ansic: 10; makefile: 6
file content (85 lines) | stat: -rw-r--r-- 1,985 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
{-# LANGUAGE CPP #-}

module Main where

import Control.Monad.State (evalState, put, get)
import Data.Bits
import Data.Chimera
import Test.Tasty.Bench
import Test.Tasty.Patterns.Printer
import System.Random

#ifdef MIN_VERSION_ral
import qualified Data.RAList as RAL
#endif

sizes :: Num a => [a]
sizes = [7, 8, 9, 10]

main :: IO ()
main = defaultMain $ (: []) $ mapLeafBenchmarks addCompare $ bgroup "read"
  [ bgroup chimeraBenchName (map benchReadChimera sizes)
  , bgroup "List"           (map benchReadList    sizes)
#ifdef MIN_VERSION_ral
  , bgroup "RAL"            (map benchReadRAL     sizes)
#endif
  ]

chimeraBenchName :: String
chimeraBenchName = "Chimera"

addCompare :: ([String] -> Benchmark -> Benchmark)
addCompare (size : name : path)
  | name /= chimeraBenchName
  = bcompare (printAwkExpr (locateBenchmark (size : chimeraBenchName : path)))
addCompare _ = id

randomChimera :: UChimera Int
randomChimera = flip evalState (mkStdGen 42) $ tabulateM $ const $ do
  g <- get
  let (x, g') = random g
  put g'
  pure x

randomList :: [Int]
randomList = randoms (mkStdGen 42)

#ifdef MIN_VERSION_ral
randomRAL :: RAL.RAList Int
randomRAL = RAL.fromList $ take (1 `shiftL` (maximum sizes)) $ randoms (mkStdGen 42)
#endif

randomIndicesWord :: [Word]
randomIndicesWord = randoms (mkStdGen 42)

randomIndicesInt :: [Int]
randomIndicesInt = randoms (mkStdGen 42)

benchReadChimera :: Int -> Benchmark
benchReadChimera k
  = bench (show n)
  $ nf (sum . map (index randomChimera))
  $ map (.&. (n - 1))
  $ take (fromIntegral n) randomIndicesWord
  where
    n = 1 `shiftL` k

benchReadList :: Int -> Benchmark
benchReadList k
  = bench (show n)
  $ nf (sum . map (randomList !!))
  $ map (.&. (n - 1))
  $ take n randomIndicesInt
  where
    n = 1 `shiftL` k

#ifdef MIN_VERSION_ral
benchReadRAL :: Int -> Benchmark
benchReadRAL k
  = bench (show n)
  $ nf (sum . map (randomRAL RAL.!))
  $ map (.&. (n - 1))
  $ take n randomIndicesInt
  where
    n = 1 `shiftL` k
#endif