Open thoughtpolice opened 8 years ago
I've managed to quickly implement this myself and I'm pretty happy with the results!
First, the harness:
{-# LANGUAGE ScopedTypeVariables #-}
module AAP.Test.Fancy
( SimulatedTestResult(..) -- :: *
, simulationTest -- :: ...
) where
import GHC.TypeLits (KnownNat)
import Prelude hiding ((!!))
import CLaSH.Signal (Signal, fromList, sampleN)
import CLaSH.Signal.Explicit (Signal', SClock, register', systemClock)
import CLaSH.Signal.Bundle (unbundle')
import CLaSH.Sized.Index (Index)
import CLaSH.Sized.Vector (Vec, (!!), maxIndex)
import CLaSH.Promoted.Nat (SNat, snat, snatToInteger)
import CLaSH.Prelude.Testbench (assert')
data SimulatedTestResult
= TestOK -- ^ Test passed
| TestFailed String -- ^ Test failed
| TestsDone -- ^ No more tests
deriving (Eq, Show)
simulatedOutputVerifier :: forall l a . (KnownNat l, Eq a, Show a)
=> Vec l a
-- ^ Samples to compare with
-> Signal a
-- ^ Signal to verify
-> Signal SimulatedTestResult
-- ^ Output signal indicating test result
simulatedOutputVerifier = simulatedOutputVerifier' systemClock
simulatedOutputVerifier' :: forall l clk a . (KnownNat l, Eq a, Show a)
=> SClock clk
-- ^ Clock to which the input signal is synchronized to
-> Vec l a
-- ^ Samples to compare with
-> Signal' clk a
-- ^ Signal to verify
-> Signal' clk SimulatedTestResult
-- ^ Indicator that all samples are verified
simulatedOutputVerifier' clk samples i =
let (s,o) = unbundle' clk (genT <$> register' clk 0 s)
(e,f) = unbundle' clk o
in simulatedAssert' clk "outputVerifier" i e (register' clk TestOK f)
where
genT :: Index l -> (Index l,(a, SimulatedTestResult))
genT s = (s',(samples !! s,finished))
where
maxI = toEnum (maxIndex samples)
s' = if s < maxI
then s + 1
else s
finished = if s == maxI then TestsDone else TestOK
simulatedAssert' :: (Eq a,Show a)
=> SClock t
-> String -- ^ Additional message
-> Signal' t a -- ^ Checked value
-> Signal' t a -- ^ Expected value
-> Signal' t SimulatedTestResult
-> Signal' t SimulatedTestResult
simulatedAssert' clk msg checked expected returned =
(\c e cnt r ->
if c == e
then r
else TestFailed (concat [ "\ncycle(" ++ show clk ++ "): "
, show cnt
, ", "
, msg
, "\nexpected value: "
, show e
, ", not equal to actual value: "
, show c
]))
<$> checked <*> expected <*> fromList [(0::Integer)..] <*> returned
-- | Run a test in simulation mode, and give a friendly report of the results.
--
-- __NB__: This function CANNOT be synthesized; it is merely a more
-- user-friendly test interface, meant so you can easily run your tests inside
-- of CLaSH. To create test benches which can be synthesized, see
-- @'CLaSH.Prelude.Testbench'@.
simulationTest :: forall a n. (Eq a, Show a, KnownNat n)
=> Vec n a -- ^ Expected list of outputs from a given signal.
-> Signal a -- ^ Input signal
-> [SimulatedTestResult]
simulationTest out inp = sampleN n (simulatedOutputVerifier out inp)
where n = fromIntegral (snatToInteger (snat :: SNat n))
Now my new tests can look like this:
module AAP.Test.Decoder16
( -- * Synthesis testing.
topEntity -- :: Signal (BitVector 16) -> Signal Instr
, testInput -- :: Signal (BitVector 16)
, expectedOutput -- :: Signal Instr -> Signal Bool
-- * Simulation testing.
, simulationOutput -- :: [SimulationTestResult]
) where
import CLaSH.Prelude
import AAP.Decoder
import AAP.Test.Fancy
--------------------------------------------------------------------------------
-- Test description
-- | Trivial circuit for testing the 16 bit instruction decoder.
topEntity :: Signal (BitVector 16) -> Signal Instr
topEntity = fmap decode16
-- | The number of tests in this test bench.
type NumTests = (3 :: Nat)
-- | Inputs into the test bench; these are run through @'topEntity'@ and checked
-- against @'output'@.
input :: Vec NumTests (BitVector 16)
input = 0b0000000000000010
:> 0b1110001100000101
:> 0b1111100000000110
:> Nil
-- | Expected outputs from running @'topEntity'@ on the test @'input'@.
output :: Vec NumTests Instr
output = map Instr16 vals where
vals = ADD16 0 0 0
:> SUB16 7 4 3
:> AND16 3 7 0
:> Nil
--------------------------------------------------------------------------------
-- Synthesis test harness.
-- | Input value signal for synthesis tests.
testInput :: Signal (BitVector 16)
testInput = stimuliGenerator input
-- | Output verifier for synthesis tests.
expectedOutput :: Signal Instr -> Signal Bool
expectedOutput = outputVerifier output
--------------------------------------------------------------------------------
-- Simulation test harness
-- | Results of running all the tests. __NB__: This is only meant for running
-- CLaSH simulation tests.
simulationOutput :: [SimulatedTestResult]
simulationOutput = simulationTest output (topEntity testInput)
Which I think is pretty good! I mean, the actual implementation could be simplified probably, but I just copy/pasted to make it as fast as possible.
@thoughtpolice Thanks again for the write up. In general I really like the suggestion(s). I think something like this can be added to the 0.7 release of CLaSH.
@christiaanb Sure, I have this module working, under the namespace CLaSH.Testbench.Fancy
in an extras package. I'd be willing to port it to 0.7 in master
and make a PR adding it, if you want, or something like it, since it looks like master
will be 0.7.
I've actually slightly tweaked it since the post the other day, and probably will continue to tweak it slightly. For example, it'd probably be even nicer to have TestFailed
contain the actual clock value, and expected/encountered values non-String
-ified, if it doesn't make plumbing things around too ugly. Then you can make just make the current error formatter the Show
instance or something.
@thoughtpolice Yes, please submit a PR to master
once you're done tweaking. If it isn't already done by me, perhaps in the process you can also refactor some of the duplicate definitions in the CLaSH.Testbench
module: for example, both stimuliGenerator
and outputVerifier
use the same sample generator in their where
clause.
Here's an example of a test bench I have for something I'm working on. This is actually only a single test bench, stressing one part of the design; I have other tests that stress other things. It simply tests that some examples of using the instruction decoder work.
My intent is to be able to test this:
iverilog
orverilator
on the results of the CLaSH compiler. This works pretty great today withiverilog
.arachne-pnr
, resulting in a description of the synthesized netlist. This is mostly a toolchain issue (.e.g getting the full netlist back, so you can plug it up to your test).topEntity
, specific to that board/hardware/test. CLaSH probably can't automate away anything more than it already does, here.Together these all provide relatively high assurance that the design works on all fronts. This ticket is mostly about the first one, which is my primary line of testing as it's far less cumbersome and much more interactive.
OK, so here's my example.
So I have this, and now there's the question.
How do I test it with CLaSH?
The CLaSH simulation can be tested, roughly, like this (with
clash --interactive
):This output is expected, although it is unintuitive.
expectedOutput
returnsFalse
while it still has samples to verify, and returnsTrue
once it has verified the last sample. Thus, stopping at the firstTrue
value gives a list, the length of which is the length of thetestInput
signal (.e.length (toList testInput)
== the number of tests in this test bench, basically).However, if the test fails, this results in something like this:
This isn't really great. Essentially, there's some
unsafePerformIO
going on somewhere that throws an exception when some particular sampled result fromtopEntity
isn't the expected result.The reason for this interface is somewhat obvious, though: The CLaSH simulation can call
trace
orerror
, or$print
or whatever in the iverilog test bench when something goes wrong, but that's an implementation detail of the test bench. That has nothing to do with the result of the compiler, or whether or not the actual functionstestInput
andexpectedOutput
can be synthesized. It is not exposed to the person writing the tests. The test itself being synthesizable in this way is desirable.The problem is this makes running the CLaSH simulation tests is really weird, IMO, with this interface. Remember, I have multiple test benches like this one, each in a different module/file stressing multiple parts of the design (or intend to): instruction fetch, 32-bit decode, the register file, etc. So this is one among many.
My build system can, relatively trivially, simply find all these files and do its business. Let's say it runs
clash --verilog path/to/Decode16.hs
on each one (to generate the verilog), and then it could run something likeclash -e AAP.Test.Decode16.fullSimulationTest path/to/Decode16.hs
to run the simulation in the interpreter.If the result of that command outputs
[False, False, False]
it passes, otherwise it fails. But this isn't great, because I have to do some weird hacky grep-like thing to determine test failure. Maybe I check that the exact string is output (but this is brittle). Or maybe I just check for any error messages (maybe less brittle). Or maybe I write some wrapper around the[Bool]
output that does some crazy stuff to silently gobble results/exceptions fromtrace
using some weird ancient unix voodoo or something, and then determine if evaluating the spine of the result gave out any impure behavior (god please no).But this is Haskell! There should just be a type specifying what happened.
Hairbrained idea
Here's my suggestion: let the test bench for simulations have some kind of interface like this:
The problem is that
String
cannot be synthesized (re: implementation detail of the simulation). But that's fine!While I originally thought that maybe this needs some hacking in the compiler, perhaps it does not. This interface can just be an extension of the current interface, and not break anything. For example, given the scheme in 0.6, this could be the exposed interface from my module
simulatedOutput
needs no special care from the compiler, it can just be completely ignored - and that's OK, because we only wanted to test it with simulation anyway!The only change this would imply is the intrudction of
simulatedOutputVerifier
andSimulationTestResult
.If I had
simulatedOutput
exported from my module, then having a higher-level module export it would let me do something like:This would allow me to hook up this interface or abstract over it in a number of ways to a bigger, more complete test driver that tests multiple components.
Anyway, that's my basic complaint. Any thoughts?