@@ -2,6 +2,8 @@ module Clash.Testbench.Generate where
2
2
3
3
import Hedgehog
4
4
import Hedgehog.Gen
5
+ import Control.Monad.State.Lazy (liftIO , get )
6
+ import Data.IORef (newIORef , readIORef , writeIORef )
5
7
6
8
import Clash.Prelude (KnownDomain (.. ), BitPack (.. ), NFDataX )
7
9
@@ -10,15 +12,138 @@ import Clash.Testbench.Internal.ID
10
12
import Clash.Testbench.Internal.Signal hiding (TBSignal , TBClock , TBReset , TBEnable )
11
13
import Clash.Testbench.Internal.Monad
12
14
15
+ matchIOGen ::
16
+ (NFDataX i , BitPack i , KnownDomain dom , Eq o , Show o ) =>
17
+ TBSignal dom o -> Gen (i , o ) -> TB (TBSignal dom i )
18
+ matchIOGen expectedOutput gen = do
19
+ ST {.. } <- get
20
+
21
+ vRef <- liftIO $ newIORef undefined
22
+ simStepCache <- liftIO (readIORef simStepRef >>= newIORef)
23
+
24
+ mind SomeSignal $ IOInput
25
+ { signalId = NoID
26
+ , signalCurVal = do
27
+ v <- readIORef simStepRef
28
+ v' <- readIORef simStepCache
29
+
30
+ if v == v'
31
+ then readIORef vRef
32
+ else do
33
+ (i, o) <- sample gen
34
+ signalExpect expectedOutput $ Expectation (v + 1 , verify o)
35
+
36
+ writeIORef vRef i
37
+ writeIORef simStepCache v
38
+ return i
39
+ , signalPrint = Nothing
40
+ }
41
+ where
42
+ verify x y
43
+ | x == y = Nothing
44
+ | otherwise = Just $ " Expected " <> show x <> " but the output is " <> show y
45
+
46
+
47
+ matchIOGenN ::
48
+ (NFDataX i , BitPack i , KnownDomain dom , Eq o , Show o ) =>
49
+ TBSignal dom o -> Gen [(i , o )] -> TB (TBSignal dom i )
50
+ matchIOGenN expectedOutput gen = do
51
+ ST {.. } <- get
52
+
53
+ vRef <- liftIO $ newIORef []
54
+ simStepCache <- liftIO (readIORef simStepRef >>= newIORef)
55
+
56
+ mind SomeSignal $ IOInput
57
+ { signalId = NoID
58
+ , signalCurVal = do
59
+ v <- readIORef simStepRef
60
+ v' <- readIORef simStepCache
61
+
62
+ if v == v'
63
+ then readIORef vRef >>= \ case
64
+ (i, _) : _ -> return i
65
+ [] -> do
66
+ (i, o) : xr <- sample gen
67
+ writeIORef vRef ((i, o) : xr)
68
+ return i
69
+ else do
70
+ writeIORef simStepCache v
71
+ readIORef vRef >>= \ case
72
+ _ : (i, o) : xr -> do
73
+ writeIORef vRef ((i, o) : xr)
74
+ signalExpect expectedOutput $ Expectation (v, verify o)
75
+ return i
76
+ _ -> do
77
+ (i, o) : xr <- sample gen
78
+ writeIORef vRef ((i, o) : xr)
79
+ signalExpect expectedOutput $ Expectation (v, verify o)
80
+ return i
81
+ , signalPrint = Nothing
82
+ }
83
+ where
84
+ verify x y
85
+ | x == y = Nothing
86
+ | otherwise = Just $ " Expected '" <> show x <> " ' but the output is '" <> show y <> " '"
87
+
88
+
13
89
generate ::
14
90
(NFDataX a , BitPack a , KnownDomain dom ) =>
15
- Gen a -> TB (TBSignal dom a )
16
- generate generator =
17
- mindSignal Generator
91
+ a -> Gen a -> TB (TBSignal dom a )
92
+ generate def gen = do
93
+ ST {.. } <- get
94
+
95
+ vRef <- liftIO $ newIORef def
96
+ simStepCache <- liftIO (readIORef simStepRef >>= newIORef)
97
+
98
+ mind SomeSignal IOInput
18
99
{ signalId = NoID
19
- , signalCurVal = sample generator
100
+ , signalCurVal = do
101
+ v <- readIORef simStepRef
102
+ v' <- readIORef simStepCache
103
+
104
+ if v == v'
105
+ then readIORef vRef
106
+ else do
107
+ x <- sample gen
108
+ writeIORef vRef x
109
+ writeIORef simStepCache v
110
+ return x
20
111
, signalPrint = Nothing
21
- , ..
22
112
}
23
113
24
-
114
+ generateN ::
115
+ (NFDataX a , BitPack a , KnownDomain dom ) =>
116
+ a -> Gen [a ] -> TB (TBSignal dom a )
117
+ generateN def gen = do
118
+ ST {.. } <- get
119
+
120
+ vRef <- liftIO $ newIORef [def]
121
+ simStepCache <- liftIO (readIORef simStepRef >>= newIORef)
122
+
123
+ mindSignal IOInput
124
+ { signalId = NoID
125
+ , signalCurVal = do
126
+ v <- readIORef simStepRef
127
+ v' <- readIORef simStepCache
128
+
129
+ if v == v'
130
+ then readIORef vRef >>= \ case
131
+ x : _ -> return x
132
+ [] -> do
133
+ x : xr <- sample gen
134
+ writeIORef vRef (x : xr)
135
+ return x
136
+
137
+ else do
138
+ writeIORef simStepCache v
139
+ readIORef vRef >>= \ case
140
+ _ : x : xr -> do
141
+ writeIORef vRef (x : xr)
142
+ return x
143
+ _ -> do
144
+ x : xr <- sample gen
145
+ writeIORef vRef (x : xr)
146
+ return x
147
+ , signalPrint = Nothing
148
+ , ..
149
+ }
0 commit comments