Skip to content

Commit

Permalink
Selectively use tools with flags
Browse files Browse the repository at this point in the history
It is now possible to selectively enable tests which use a
specific vendor tool by passing a flag to the testsuite driver,
e.g. --verilator for running tests with verilator. If a tool is not
given it's tests pass (as the tasty API does not allow deciding to
skip a test inside IsTest.run). If the tool is not found the error
is not tidied up instead of showing the contents of stderr.

This is a somewhat crude first attempt at addressing #2012.
  • Loading branch information
Alex McKenna committed Dec 10, 2021
1 parent 7d188ce commit a42d822
Show file tree
Hide file tree
Showing 9 changed files with 352 additions and 198 deletions.
6 changes: 3 additions & 3 deletions .ci/gitlab/test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -83,14 +83,14 @@ prelude:doctests:
suite:vhdl:
extends: .test-common-local
script:
- cabal v2-run -- clash-testsuite -j$THREADS -p .VHDL --hide-successes
- cabal v2-run -- clash-testsuite -j$THREADS -p .VHDL --hide-successes --ghdl

suite:verilog:
extends: .test-common-local
script:
- cabal v2-run -- clash-testsuite -j$THREADS -p .Verilog --hide-successes
- cabal v2-run -- clash-testsuite -j$THREADS -p .Verilog --hide-successes --iverilog --verilator

suite:systemverilog:
extends: .test-common-local
script:
- cabal v2-run -- clash-testsuite -j$THREADS -p .SystemVerilog --hide-successes
- cabal v2-run -- clash-testsuite -j$THREADS -p .SystemVerilog --hide-successes --verilator
7 changes: 5 additions & 2 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,10 @@ jobs:
cabal v2-test clash-cosim
- name: Testsuite (VHDL)
run: cabal v2-run clash-testsuite -- -j$THREADS --hide-successes -p .VHDL
run: cabal v2-run clash-testsuite -- -j$THREADS --hide-successes -p .VHDL --ghdl

- name: Testsuite (Verilog)
run: cabal v2-run clash-testsuite -- -j$THREADS --hide-successes -p .Verilog
run: cabal v2-run clash-testsuite -- -j$THREADS --hide-successes -p .Verilog --iverilog --verilator

- name: Testsuite (SystemVerilog)
run: cabal v2-run clash-testsuite -- -j$THREADS --hide-successes -p .SystemVerilog --verilator
2 changes: 2 additions & 0 deletions tests/clash-testsuite.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,9 @@ common basic-config
Glob >=0.9 && <1.0,
ieee754,
neat-interpolation >=0.3 && <0.6,
optparse-applicative,
process >=1.2 && <1.7,
tagged,
tasty >=1.2 && <1.4,
tasty-hunit,
temporary,
Expand Down
144 changes: 85 additions & 59 deletions tests/src/Test/Tasty/Clash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -301,14 +301,14 @@ vhdlTests
vhdlTests opts@TestOptions{..} tmpDir = (buildTests, simTests)
where
importName = "GHDL (import)"
makeName t = "GHDL (make " <> t <> ")"
makeName t = "ghdl (make " <> t <> ")"
buildTests = concat
[ [ (importName, singleTest importName (GhdlImportTest tmpDir)) ]
, [ (makeName t, singleTest (makeName t) (GhdlMakeTest tmpDir t))
| t <- getBuildTargets opts ]
]

simName t = "GHDL (sim " <> t <> ")"
simName t = "ghdl (sim " <> t <> ")"
simTests =
[ (simName t, singleTest (simName t) (GhdlSimTest expectSimFail tmpDir t))
| t <- getBuildTargets opts
Expand All @@ -325,39 +325,16 @@ verilogTests
verilogTests opts@TestOptions{..} tmpDir = (buildTests, simTests)
where
makeNameIvl t = "iverilog (make " <> t <> ")"
ivlMake =
buildTests =
[ (makeNameIvl t, singleTest (makeNameIvl t) (IVerilogMakeTest tmpDir t))
| t <- getBuildTargets opts
]

makeNameVer t = "verilator (make " <> t <> ")"
verMake =
[ (makeNameVer t, singleTest (makeNameVer t) (VerilatorMakeTest tmpDir t))
| t <- getBuildTargets opts
]

buildTests =
case verilate of
SimAndVerilate -> ivlMake <> verMake
VerilateOnly -> verMake
SimOnly -> ivlMake

simNameIvl t = "iverilog (sim " <> t <> ")"
ivlSim =
simTests =
[ (simNameIvl t, singleTest (simNameIvl t) (IVerilogSimTest expectSimFail vvpStdoutNonEmptyFail tmpDir t))
| t <- getBuildTargets opts
]
simNameVer t = "verilator (sim " <> t <> ")"
verSim =
[ (simNameVer t, singleTest (simNameVer t) (VerilatorSimTest expectSimFail vvpStdoutNonEmptyFail tmpDir t))
| t <- getBuildTargets opts
]

simTests =
case verilate of
SimAndVerilate -> ivlSim <> verSim
VerilateOnly -> verSim
SimOnly -> ivlSim

-- | Generate two test trees for testing SystemVerilog: one for building designs and
-- one for running them. Depending on 'hdlSim' the latter will be executed or not.
Expand All @@ -371,40 +348,37 @@ systemVerilogTests opts@TestOptions{..} tmpDir = (buildTests, simTests)
where
vlibName = "modelsim (vlib)"
vlogName = "modelsim (vlog)"
msimMake =
buildTests =
[ (vlibName, singleTest vlibName (ModelsimVlibTest tmpDir))
, (vlogName, singleTest vlogName (ModelsimVlogTest tmpDir))
]

verName t = "verilator (make " <> t <> ")"
verMake =
[ (verName t, singleTest (verName t) (VerilatorMakeTest tmpDir t))
| t <- getBuildTargets opts
]

buildTests =
case verilate of
SimAndVerilate -> msimMake <> verMake
VerilateOnly -> verMake
SimOnly -> msimMake

simName t = "modelsim (sim " <> t <> ")"
msimSim =
simTests =
[ (simName t, singleTest (simName t) (ModelsimSimTest expectSimFail tmpDir t))
| t <- getBuildTargets opts
]

simNameVer t = "verilator (sim " <> t <> ")"
verSim =
[ (simNameVer t, singleTest (simNameVer t) (VerilatorSimTest expectSimFail vvpStdoutNonEmptyFail tmpDir t))
verilatorTests
:: TestOptions
-> IO FilePath
-> ( [(TestName, TestTree)]
, [(TestName, TestTree)]
)
verilatorTests opts@TestOptions{..} tmpDir = (buildTests, simTests)
where
buildName t = "verilator (make " <> t <> ")"
simName t = "verilator (sim " <> t <> ")"

buildTests =
[ (buildName t, singleTest (buildName t) (VerilatorMakeTest tmpDir t))
| t <- getBuildTargets opts
]

simTests =
case verilate of
SimAndVerilate -> msimSim <> verSim
VerilateOnly -> verSim
SimOnly -> msimSim
[ (simName t, singleTest (simName t) (VerilatorSimTest expectSimFail vvpStdoutNonEmptyFail tmpDir t))
| t <- getBuildTargets opts
]

-- | Generate a test tree for running SymbiYosys
sbyTests :: TestOptions -> IO FilePath -> ([(TestName, TestTree)])
Expand All @@ -424,17 +398,12 @@ runTest1
-> TestTree
runTest1 modName opts@TestOptions{..} path target =
withResource mkTmpDir Directory.removeDirectoryRecursive $ \tmpDir -> do
testGroup (show target) $ sequenceTests (show target:path) $ clashTest tmpDir :
(case target of
VHDL -> buildAndSimTests (vhdlTests opts tmpDir)
Verilog -> buildAndSimTests (verilogTests opts tmpDir)
SystemVerilog-> buildAndSimTests (systemVerilogTests opts tmpDir)
) <>
(case verificationTool of
Nothing -> []
Just SymbiYosys -> sbyTests opts tmpDir
)

testGroup (show target) $
sequenceTests (show target : path) (clashTest tmpDir : nonVerilator tmpDir)
<> tail (sequenceTests (show target : path) (clashTest tmpDir : verilator tmpDir))
<> (case verificationTool of
Nothing -> []
Just SymbiYosys -> tail $ sequenceTests (show target : path) (clashTest tmpDir : sbyTests opts tmpDir))
where
mkTmpDir = flip createTempDirectory "clash-test" =<< getCanonicalTemporaryDirectory
sourceDir = List.foldl' (</>) sourceDirectory (reverse (tail path))
Expand All @@ -456,6 +425,63 @@ runTest1 modName opts@TestOptions{..} path target =
(_, _, False) -> buildTests
_ -> buildTests <> simTests

{-
buildAndSimTests name (buildTests, simTests)
-- Nothing
| isJust expectClashFail || not hdlLoad
= []
-- Build only
| not hdlSim
= [(name, testGroup name $ sequenceTests (show target : path) buildTests)]
-- Build and simulate
| otherwise
= [(name, testGroup name $ sequenceTests (show target : path) (buildTests <> simTests))]
-}

-- HACK: We want to run verilator and simulator tests independently if they
-- are both going to be run, otherwise failures from whichever comes first
-- will mean the second is skipped. In lieu of a better way to sequence tests
-- we can sequence tests for multiple simulators, then drop the first test
-- tree for all but the first simulator (as it will be copies of clash gen).
--
-- TODO: Since tasty doesn't provide one, we should really provide a better
-- set of combinators for describing test dependencies. That way we can have
-- some more principled way of having a test structure like
--
-- Group A
-- - Task A1
-- - Group B
-- - Task B1
-- - Task B2
-- - Group C
-- - Task C1
--
-- where groups B and C are independent of each other, but both dependent on
-- the success of Task A1.

nonVerilator tmpDir =
case target of
VHDL -> buildAndSimTests (vhdlTests opts tmpDir)
Verilog ->
case verilate of
VerilateOnly -> []
_ -> buildAndSimTests (verilogTests opts tmpDir)

SystemVerilog ->
case verilate of
VerilateOnly -> []
_ -> buildAndSimTests (systemVerilogTests opts tmpDir)

verilator tmpDir =
case target of
VHDL -> []
_ ->
case verilate of
SimOnly -> []
_ -> buildAndSimTests (verilatorTests opts tmpDir)

runTest
:: String
-- ^ Name of test
Expand Down
88 changes: 58 additions & 30 deletions tests/src/Test/Tasty/Ghdl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,16 +9,30 @@ import Control.Monad (foldM, forM_)
import Data.Char (toLower)
import Data.Coerce (coerce)
import qualified Data.List as List
import Data.Proxy
import Data.Tagged
import qualified Data.Text as T
import System.Directory (createDirectory, listDirectory, copyFile)
import System.FilePath ((</>), replaceFileName)
import System.FilePath.Glob (glob)

import Test.Tasty.Common
import Test.Tasty.Options
import Test.Tasty.Program
import Test.Tasty.Providers
import Test.Tasty.Runners

-- | @--ghdl@ flag for enabling tests that use GHDL.
newtype Ghdl = Ghdl Bool
deriving (Eq, Ord)

instance IsOption Ghdl where
defaultValue = Ghdl False
parseValue = fmap Ghdl . safeReadBool
optionName = pure "ghdl"
optionHelp = pure "Use GHDL for tests"
optionCLParser = flagCLParser Nothing (Ghdl True)

-- | Search through a directory with VHDL files produced by Clash
-- and produces /work/ files using @ghdl -i@ for each library.
--
Expand All @@ -40,12 +54,16 @@ data GhdlImportTest = GhdlImportTest
}

instance IsTest GhdlImportTest where
run optionSet GhdlImportTest{gitSourceDirectory} progressCallback = do
src <- gitSourceDirectory
let workDir = src </> "work"
createDirectory workDir
manifests <- getManifests (src </> "*" </> manifestFilename)
foldM (goManifest workDir) (testPassed "") manifests
run optionSet GhdlImportTest{gitSourceDirectory} progressCallback
| Ghdl True <- lookupOption optionSet = do
src <- gitSourceDirectory
let workDir = src </> "work"
createDirectory workDir
manifests <- getManifests (src </> "*" </> manifestFilename)
foldM (goManifest workDir) (testPassed "") manifests

| otherwise =
pure (testPassed "Ignoring test: Use --ghdl to run")
where
stdArgs = ["-i", "--std=93"]
runGhdlI workDir args =
Expand All @@ -67,7 +85,8 @@ instance IsTest GhdlImportTest where

| otherwise = pure result

testOptions = coerce (testOptions @TestProgram)
testOptions =
coerce (coerce (testOptions @TestProgram) <> [Option (Proxy @Ghdl)])

-- | Create an executable given directory 'GhdlImportTest' produced work files
-- in.
Expand All @@ -86,20 +105,24 @@ data GhdlMakeTest = GhdlMakeTest
}

instance IsTest GhdlMakeTest where
run optionSet GhdlMakeTest{gmtSourceDirectory,gmtTop} progressCallback = do
src <- gmtSourceDirectory
let
workDir = src </> "work"
libs <- listDirectory workDir
runGhdl workDir $
["-m", "-fpsl", "--work=" <> gmtTop, "--workdir=" <> gmtTop]
<> ["-P" <> lib | lib <- libs]
<> ["-o", map toLower (gmtTop <> "_exe"), gmtTop]
run optionSet GhdlMakeTest{gmtSourceDirectory,gmtTop} progressCallback
| Ghdl True <- lookupOption optionSet = do
src <- gmtSourceDirectory
let workDir = src </> "work"
libs <- listDirectory workDir
runGhdl workDir $
["-m", "-fpsl", "--work=" <> gmtTop, "--workdir=" <> gmtTop]
<> ["-P" <> lib | lib <- libs]
<> ["-o", map toLower (gmtTop <> "_exe"), gmtTop]

| otherwise =
pure (testPassed "Ignoring test: Use --ghdl to run")
where
ghdl workDir args = TestProgram "ghdl" args NoGlob PrintNeither False (Just workDir)
runGhdl workDir args = run optionSet (ghdl workDir args) progressCallback

testOptions = coerce (testOptions @TestProgram)
testOptions =
coerce (coerce (testOptions @TestProgram) <> [Option (Proxy @Ghdl)])

-- | Run executable generated by 'GhdlMakeTest'.
--
Expand All @@ -119,18 +142,22 @@ data GhdlSimTest = GhdlSimTest
}

instance IsTest GhdlSimTest where
run optionSet GhdlSimTest{..} progressCallback = do
src <- gstSourceDirectory
let workDir = src </> "work"

-- See Note [copy data files hack]
lists <- glob (src </> "*/memory.list")
forM_ lists $ \memFile ->
copyFile memFile (workDir </> "memory.list")

case gstExpectFailure of
Nothing -> run optionSet (program workDir gstTop) progressCallback
Just exit -> run optionSet (failingProgram workDir gstTop exit) progressCallback
run optionSet GhdlSimTest{..} progressCallback
| Ghdl True <- lookupOption optionSet = do
src <- gstSourceDirectory
let workDir = src </> "work"

-- See Note [copy data files hack]
lists <- glob (src </> "*/memory.list")
forM_ lists $ \memFile ->
copyFile memFile (workDir </> "memory.list")

case gstExpectFailure of
Nothing -> run optionSet (program workDir gstTop) progressCallback
Just exit -> run optionSet (failingProgram workDir gstTop exit) progressCallback

| otherwise =
pure (testPassed "Ignoring test: Use --ghdl to run")
where
program workDir top =
TestProgram "ghdl" (args top) NoGlob PrintNeither False (Just workDir)
Expand All @@ -148,4 +175,5 @@ instance IsTest GhdlSimTest where
, "--assert-level=error"
]

testOptions = coerce (testOptions @TestProgram)
testOptions =
coerce (coerce (testOptions @TestProgram) <> [Option (Proxy @Ghdl)])
Loading

0 comments on commit a42d822

Please sign in to comment.