Copyright | (C) 2013-2016 University of Twente 2017 Google Inc. 2019 Myrtle Software Ltd |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Extensions |
|
Synopsis
- assert :: (Eq a, ShowX a, HiddenClock dom, HiddenReset dom) => String -> Signal dom a -> Signal dom a -> Signal dom b -> Signal dom b
- assertBitVector :: (KnownNat n, HiddenClock dom, HiddenReset dom) => String -> Signal dom (BitVector n) -> Signal dom (BitVector n) -> Signal dom b -> Signal dom b
- ignoreFor :: HiddenClockResetEnable dom => SNat n -> a -> Signal dom a -> Signal dom a
- outputVerifier' :: (KnownNat l, Eq a, ShowX a, HiddenClock dom, HiddenReset dom) => Vec l a -> Signal dom a -> Signal dom Bool
- outputVerifierBitVector' :: (KnownNat l, KnownNat n, HiddenClock dom, HiddenReset dom) => Vec l (BitVector n) -> Signal dom (BitVector n) -> Signal dom Bool
- stimuliGenerator :: (KnownNat l, HiddenClock dom, HiddenReset dom) => Vec l a -> Signal dom a
- tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom
- tbEnableGen :: Enable tag
- tbSystemClockGen :: Signal System Bool -> Clock System
Testbench functions for circuits
:: (Eq a, ShowX a, HiddenClock dom, HiddenReset dom) | |
=> String | Additional message |
-> Signal dom a | Checked value |
-> Signal dom a | Expected value |
-> Signal dom b | Return value |
-> Signal dom b |
Compares the first two Signal
s for equality and logs a warning when they
are not equal. The second Signal
is considered the expected value. This
function simply returns the third Signal
unaltered as its result. This
function is used by outputVerifier'
.
NB: This function can be used in synthesizable designs.
:: (KnownNat n, HiddenClock dom, HiddenReset dom) | |
=> String | Additional message |
-> Signal dom (BitVector n) | Checked value |
-> Signal dom (BitVector n) | Expected value |
-> Signal dom b | Return value |
-> Signal dom b |
The same as assert
, but can handle don't care bits in it's expected value.
:: HiddenClockResetEnable dom | |
=> SNat n | Number of cycles to ignore incoming signal |
-> a | Value function produces when ignoring signal |
-> Signal dom a | Incoming signal |
-> Signal dom a | Either a passthrough of the incoming signal, or the static value provided as the second argument. |
Ignore signal for a number of cycles, while outputting a static value.
:: (KnownNat l, Eq a, ShowX a, HiddenClock dom, HiddenReset dom) | |
=> Vec l a | Samples to compare with |
-> Signal dom a | Signal to verify |
-> Signal dom Bool | Indicator that all samples are verified |
Example:
expectedOutput :: HiddenClockResetEnable dom ->Signal
dom Int ->Signal
dom Bool expectedOutput =outputVerifier'
$(listToVecTH
([70,99,2,3,4,5,7,8,9,10]::[Int]))
>>>
import qualified Data.List as List
>>>
sampleN @System 12 (expectedOutput (fromList (0:[0..10] List.++ [10,10,10])))
cycle(<Clock: System>): 0, outputVerifier expected value: 70, not equal to actual value: 0 [False cycle(<Clock: System>): 1, outputVerifier expected value: 70, not equal to actual value: 0 ,False cycle(<Clock: System>): 2, outputVerifier expected value: 99, not equal to actual value: 1 ,False,False,False,False,False cycle(<Clock: System>): 7, outputVerifier expected value: 7, not equal to actual value: 6 ,False cycle(<Clock: System>): 8, outputVerifier expected value: 8, not equal to actual value: 7 ,False cycle(<Clock: System>): 9, outputVerifier expected value: 9, not equal to actual value: 8 ,False cycle(<Clock: System>): 10, outputVerifier expected value: 10, not equal to actual value: 9 ,False,True]
If your working with BitVector
s containing don't care bits you should use outputVerifierBitVector'
.
outputVerifierBitVector' Source #
:: (KnownNat l, KnownNat n, HiddenClock dom, HiddenReset dom) | |
=> Vec l (BitVector n) | Samples to compare with |
-> Signal dom (BitVector n) | Signal to verify |
-> Signal dom Bool | Indicator that all samples are verified |
Same as outputVerifier'
,
but can handle don't care bits in it's expected values.
:: (KnownNat l, HiddenClock dom, HiddenReset dom) | |
=> Vec l a | Samples to generate |
-> Signal dom a | Signal of given samples |
Example:
testInput :: HiddenClockResetEnable dom =>Signal
dom Int testInput =stimuliGenerator
$(listToVecTH
[(1::Int),3..21])
>>>
sampleN @System 13 testInput
[1,1,3,5,7,9,11,13,15,17,19,21,21]
tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom Source #
Clock generator to be used in the testBench function.
To be used like:
clkSystem en = tbClockGen @System en
Example
module Example where import Clash.Explicit.Prelude import Clash.Explicit.Testbench -- Fast domain: twice as fast as "Slow"createDomain
vSystem
{vName="Fast", vPeriod=10} -- Slow domain: twice as slow as "Fast"createDomain
vSystem
{vName="Slow", vPeriod=20} topEntity ::Clock
"Fast" ->Reset
"Fast" ->Enable
"Fast" ->Clock
"Slow" ->Signal
"Fast" (Unsigned 8) ->Signal
"Slow" (Unsigned 8, Unsigned 8) topEntity clk1 rst1 en1 clk2 i = let h = register clk1 rst1 en1 0 (register clk1 rst1 en1 0 i) l = register clk1 rst1 en1 0 i in unsafeSynchronizer clk1 clk2 (bundle (h, l)) testBench ::Signal
"Slow" Bool testBench = done where testInput =stimuliGenerator
clkA1 rstA1 $(listToVecTH
[1::Unsigned 8,2,3,4,5,6,7,8]) expectedOutput =outputVerifier
clkB2 rstB2 $(listToVecTH
[(0,0) :: (Unsigned 8, Unsigned 8),(1,2),(3,4),(5,6),(7,8)]) done = expectedOutput (topEntity clkA1 rstA1 enableGen clkB2 testInput) notDone = not <$> done clkA1 =tbClockGen
@"Fast" (unsafeSynchronizer clkB2 clkA1 notDone) clkB2 =tbClockGen
@"Slow" notDone rstA1 =resetGen
@"Fast" rstB2 =resetGen
@"Slow"
tbEnableGen :: Enable tag Source #
Enable signal that's always enabled. Because it has a blackbox definition this enable signal is opaque to other blackboxes. It will therefore never be optimized away.
tbSystemClockGen :: Signal System Bool -> Clock System Source #
Clock generator for the System
clock domain.
NB: can be used in the testBench function
Example
topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
topEntity = concat
testBench :: Signal System Bool
testBench = done
where
testInput = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
expectedOutput = outputVerifier ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
done = exposeClockResetEnable (expectedOutput (topEntity $ testInput)) clk rst
clk = tbSystemClockGen
(not <$> done)
rst = systemResetGen