File: BenchRAM.hs

package info (click to toggle)
haskell-clash-prelude 1.8.1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,432 kB
  • sloc: haskell: 23,509; makefile: 6
file content (148 lines) | stat: -rw-r--r-- 4,214 bytes parent folder | download | duplicates (2)
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
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
{-# LANGUAGE MagicHash, TypeApplications, DataKinds #-}
module BenchRAM (ramBench) where

import Criterion (Benchmark, env, bench, nf, bgroup, envWithCleanup)
import System.Directory
import System.IO

import Clash.Explicit.BlockRam
import Clash.Explicit.BlockRam.File
import Clash.Explicit.RAM
import Clash.Explicit.ROM
import Clash.Explicit.Signal
import Clash.Prelude.ROM
import Clash.Promoted.Nat
import Clash.Promoted.Nat.Literals
import qualified Clash.Sized.Vector as V
import Clash.Sized.Internal.BitVector (undefined#)

ramBench :: Benchmark
ramBench = bgroup "RAMs"
  [ asyncRamBench
  , asyncRomBench
  , blockRamBench
  , blockRamROBench
  , blockRamFileBench
  , blockRamFileROBench
  , romBench
  ]

asyncRamBench :: Benchmark
asyncRamBench = env setup $ \m ->
  bench "asyncRam#" $
  nf (take 298 . drop 2 . simulate_lazy
        (\rw -> let (r,w) = unbundle rw
                in  asyncRam# @System
                      clockGen
                      clockGen
                      enableGen
                      (SNat @4096)
                      r
                      (pure True)
                      w
                      w
                   )) m
  where
    setup   = pure (zip [556,557..856] [557,558..857])

asyncRomBench :: Benchmark
asyncRomBench = env setup $ \m ->
  bench "asyncRom#" $
  nf (take 98 . drop 2 . fmap (asyncRom# ramInit)) m
  where
    ramInit = V.replicate d1024 (1 :: Int)
    setup   = pure ([557,558..857])

blockRamBench :: Benchmark
blockRamBench = env setup $ \m ->
  bench "blockRam# (100% writes)" $
  nf (take 8298 . drop 2 . simulate_lazy
        (\w -> ram w
                    (pure True)
                    w
                    w
                   )) (cycle m)
  where
    ramInit = V.replicate (SNat @4096) (1 :: Int)
    setup   = pure ([557,558..857])
    ram     = blockRam# @System
                    clockGen
                    enableGen
                    ramInit

blockRamROBench :: Benchmark
blockRamROBench = env setup $ \m ->
  bench "blockRam# (0% writes)" $
  nf (take 8298 . drop 2 . simulate_lazy
        (\w -> ram w
                    (pure False)
                    w
                    w
                   )) (cycle m)
  where
    ramInit = V.replicate (SNat @4096) (1 :: Int)
    setup   = pure ([557,558..857])
    ram     = blockRam# @System
                    clockGen
                    enableGen
                    ramInit

blockRamFileBench :: Benchmark
blockRamFileBench = envWithCleanup setup cleanup $ \(~(m,_,ram)) ->
  bench "blockRamFile# (100% writes)" $
  nf (take 8298 . drop 2 . simulate_lazy
        (\w -> ram  w
                    (pure True)
                    w
                    (pure undefined#)
                   )) (cycle m)
  where
    setup = do
      (fp,h) <- openTempFile "." "mem.bin"
      hPutStr h (unlines (replicate 4096 (replicate 63 '0' ++ ['1'])))
      hClose h
      let ram = blockRamFile# @64 @System
              clockGen
              enableGen
              (SNat @4096)
              fp
      fp `seq` ram `seq` return ([557,558..857],fp,ram)

    cleanup (_,f,_) = removeFile f

blockRamFileROBench :: Benchmark
blockRamFileROBench = envWithCleanup setup cleanup $ \(~(m,_,ram)) ->
  bench "blockRamFile# (0% writes)" $
  nf (take 8298 . drop 2 . simulate_lazy
        (\w -> ram w
                   (pure False)
                   w
                   (pure undefined#)
                   )) (cycle m)
  where
    setup = do
      (fp,h) <- openTempFile "." "mem.bin"
      hPutStr h (unlines (replicate 4096 (replicate 63 '0' ++ ['1'])))
      hClose h
      let ram = blockRamFile# @64 @System
                    clockGen
                    enableGen
                    (SNat @4096)
                    fp
      fp `seq` ram `seq` return ([557,558..857], fp, ram)

    cleanup (_,f,_) = removeFile f

romBench :: Benchmark
romBench = env setup $ \m ->
  bench "rom#" $
  nf (take 98 . drop 2 . simulate_lazy
        (\r -> rom# @System
                    clockGen
                    enableGen
                    ramInit
                    r
                   )) m
  where
    ramInit = V.replicate d1024 (1 :: Int)
    setup   = pure ([557,558..857])