clash-prelude-1.2.1: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2013-2016 University of Twente
2017 Google Inc.
2019 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • ScopedTypeVariables
  • BangPatterns
  • TypeFamilies
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • MagicHash
  • KindSignatures
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Explicit.Testbench

Contents

Description

 
Synopsis

Testbench functions for circuits

assert Source #

Arguments

:: (KnownDomain dom, Eq a, ShowX a) 
=> Clock dom 
-> Reset 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 Signals 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.

assertBitVector Source #

Arguments

:: (KnownDomain dom, KnownNat n) 
=> Clock dom 
-> Reset 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.

ignoreFor Source #

Arguments

:: KnownDomain dom 
=> Clock dom 
-> Reset dom 
-> Enable 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.

stimuliGenerator Source #

Arguments

:: (KnownNat l, KnownDomain dom) 
=> Clock dom

Clock to which to synchronize the output signal

-> Reset dom 
-> Vec l a

Samples to generate

-> Signal dom a

Signal of given samples

Example:

testInput
  :: KnownDomain dom
  => Clock dom
  -> Reset dom
  -> Signal dom Int
testInput clk rst = stimuliGenerator clk rst $(listToVecTH [(1::Int),3..21])
>>> sampleN 14 (testInput systemClockGen resetGen)
[1,1,3,5,7,9,11,13,15,17,19,21,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

Expand
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)
    done'          = not <$> done
    clkA1          = tbClockGen @"Fast" (unsafeSynchronizer clkB2 clkA1 done')
    clkB2          = tbClockGen @"Slow" done'
    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

Expand
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

outputVerifier Source #

Arguments

:: (KnownNat l, KnownDomain testDom, KnownDomain circuitDom, DomainResetKind testDom ~ Asynchronous, Eq a, ShowX a) 
=> Clock testDom

Clock to which the testbench is synchronized to (but not necessarily the circuit under test)

-> Reset testDom

Reset line of testbench

-> Vec l a

Samples to compare with

-> Signal circuitDom a

Signal to verify

-> Signal testDom Bool

True if all samples are verified

Compare a signal (coming from a circuit) to a vector of samples. If a sample from the signal is not equal to the corresponding sample in the vector, print to stderr and continue testing. This function is synthesizable in the sense that HDL simulators will run it.

Example:

expectedOutput
  :: Clock dom -> Reset dom
  -> Signal dom Int -> Signal dom Bool
expectedOutput clk rst = outputVerifier clk rst $(listToVecTH ([70,99,2,3,4,5,7,8,9,10]::[Int]))
>>> import qualified Data.List as List
>>> sampleN 12 (expectedOutput systemClockGen resetGen (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 BitVectors containing don't care bits you should use outputVerifierBitVector.

outputVerifier' Source #

Arguments

:: (KnownNat l, KnownDomain dom, DomainResetKind dom ~ Asynchronous, Eq a, ShowX a) 
=> Clock dom

Clock to which the testbench is synchronized to

-> Reset dom

Reset line of testbench

-> Vec l a

Samples to compare with

-> Signal dom a

Signal to verify

-> Signal dom Bool

Indicator that all samples are verified

Same as outputVerifier but used in cases where the testbench domain and the domain of the circuit under test are the same.

outputVerifierBitVector Source #

Arguments

:: (KnownNat l, KnownNat n, KnownDomain testDom, KnownDomain circuitDom, DomainResetKind testDom ~ Asynchronous) 
=> Clock testDom

Clock to which the input signal is synchronized to

-> Reset testDom 
-> Vec l (BitVector n)

Samples to compare with

-> Signal circuitDom (BitVector n)

Signal to verify

-> Signal testDom Bool

Indicator that all samples are verified

Same as outputVerifier, but can handle don't care bits in it's expected values.

outputVerifierBitVector' Source #

Arguments

:: (KnownNat l, KnownNat n, KnownDomain dom, DomainResetKind dom ~ Asynchronous) 
=> Clock dom

Clock to which the input signal is synchronized to

-> Reset 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.

biTbClockGen :: forall testDom circuitDom. (KnownDomain testDom, KnownDomain circuitDom, DomainResetKind testDom ~ Asynchronous) => Signal testDom Bool -> (Clock testDom, Clock circuitDom) Source #

Same as tbClockGen, but returns two clocks on potentially different domains. To be used in situations where the circuit under test runs in a different domain than the circuit testing it. Most commonly used to test synchronous circuits (with an asynchronous test circuit).