diff --git a/.ci/docker/Dockerfile b/.ci/docker/Dockerfile index 766ac1da1c..bf6d9608ff 100644 --- a/.ci/docker/Dockerfile +++ b/.ci/docker/Dockerfile @@ -124,11 +124,12 @@ FROM ubuntu:$UBUNTU_VERSION AS run LABEL vendor="QBayLogic B.V." maintainer="devops@qbaylogic.com" ENV DEBIAN_FRONTEND=noninteractive LANG=C.UTF-8 LC_ALL=C.UTF-8 PATH="$PATH:/opt/bin:/root/.ghcup/bin" -ARG DEPS_RUNTIME="ca-certificates ccache curl g++ gcc git jq libc6-dev libgmp10-dev libgnat-9 libllvm11 libreadline8 libtinfo-dev libtcl8.6 make perl python3 ssh zlib1g-dev zlibc zstd" +ARG DEPS_RUNTIME="ca-certificates ccache curl g++ gcc git jq libc6-dev libgmp10-dev libgnat-9 libllvm11 libreadline8 libtinfo-dev libtcl8.6 make perl python3 ssh zlib1g-dev zlibc zstd locales libtinfo5" RUN apt-get update \ && apt-get install -y --no-install-recommends $DEPS_RUNTIME \ && apt-get clean \ - && rm -rf /var/lib/apt/lists/* + && rm -rf /var/lib/apt/lists/* \ + && locale-gen en_US.UTF-8 COPY --from=build-ghdl /opt /opt COPY --from=build-iverilog /opt /opt diff --git a/.ci/gitlab/benchmark.yml b/.ci/gitlab/benchmark.yml index 7c5e242e66..2c55d7e00d 100644 --- a/.ci/gitlab/benchmark.yml +++ b/.ci/gitlab/benchmark.yml @@ -1,5 +1,5 @@ .benchmark: - image: ghcr.io/clash-lang/clash-ci-$GHC_VERSION:2022-05-10 + image: ghcr.io/clash-lang/clash-ci-$GHC_VERSION:2022-06-18 stage: test timeout: 2 hours variables: diff --git a/.ci/gitlab/common.yml b/.ci/gitlab/common.yml index bd54ca8969..e6423ad841 100644 --- a/.ci/gitlab/common.yml +++ b/.ci/gitlab/common.yml @@ -1,5 +1,5 @@ .common: - image: ghcr.io/clash-lang/clash-ci-$GHC_VERSION:2022-05-10 + image: ghcr.io/clash-lang/clash-ci-$GHC_VERSION:2022-06-18 timeout: 2 hours stage: build variables: diff --git a/.ci/gitlab/test.yml b/.ci/gitlab/test.yml index fd6867c4ce..9523a11bb6 100644 --- a/.ci/gitlab/test.yml +++ b/.ci/gitlab/test.yml @@ -83,14 +83,62 @@ 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 --no-vivado 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 --no-vivado suite:systemverilog: extends: .test-common-local script: - - cabal v2-run -- clash-testsuite -j$THREADS -p .SystemVerilog --hide-successes --no-modelsim + - cabal v2-run -- clash-testsuite -j$THREADS -p .SystemVerilog --hide-successes --no-modelsim --no-vivado + +# Vivado is quite slow, so we only run a subset of the tests on development branches +# with it. The full testsuite gets run with Vivado every night on 'master'. +suite:cores: + extends: .test-common-local + script: + - source /opt/tools/Xilinx/Vivado/2022.1/settings64.sh + - cabal v2-run -- clash-testsuite -j$THREADS -p Cores --hide-successes --no-modelsim --no-ghdl --no-iverilog --no-verilator --no-symbiyosys + tags: + - local + - vivado-2022.1-standard + + +# Tests run on local fast machines with Vivado installed. We only run these at night +# to save resources - as Vivado is quite slow to execute. +.test-common-local-nightly: + extends: .test-common-local + rules: + - if: $CI_PIPELINE_SOURCE == "schedule" # When schedueled (at night) + - if: $CI_PIPELINE_SOURCE == "trigger" # When triggered (manual triggers) + - if: '$CI_COMMIT_TAG != null' # When tags are set (releases) + +suite:vivado:vhdl: + extends: .test-common-local #-nightly + script: + - source /opt/tools/Xilinx/Vivado/2022.1/settings64.sh + - cabal v2-run -- clash-testsuite -j$THREADS -p .VHDL --hide-successes --no-modelsim --no-ghdl --no-iverilog --no-verilator --no-symbiyosys + tags: + - local + - vivado-2022.1-standard + +suite:vivado:verilog: + extends: .test-common-local #-nightly + script: + - source /opt/tools/Xilinx/Vivado/2022.1/settings64.sh + - cabal v2-run -- clash-testsuite -j$THREADS -p .Verilog --hide-successes --no-modelsim --no-ghdl --no-iverilog --no-verilator --no-symbiyosys + tags: + - local + - vivado-2022.1-standard + +suite:vivado:systemverilog: + extends: .test-common-local #-nightly + script: + - source /opt/tools/Xilinx/Vivado/2022.1/settings64.sh + - cabal v2-run -- clash-testsuite -j$THREADS -p .SystemVerilog --hide-successes --no-modelsim --no-ghdl --no-iverilog --no-verilator --no-symbiyosys + tags: + - local + - vivado-2022.1-standard diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index 256bab89bf..7de20bdec4 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -92,7 +92,7 @@ jobs: # Run steps inside the clash CI docker image container: - image: ghcr.io/clash-lang/clash-ci-${{ matrix.ghc }}:2022-05-10 + image: ghcr.io/clash-lang/clash-ci-${{ matrix.ghc }}:2022-06-18 env: THREADS: 2 diff --git a/tests/clash-testsuite.cabal b/tests/clash-testsuite.cabal index af0cc016ba..3fb85b04cf 100644 --- a/tests/clash-testsuite.cabal +++ b/tests/clash-testsuite.cabal @@ -12,6 +12,8 @@ maintainer: Christiaan Baaij copyright: Copyright © 2015 University of Twente category: Testing build-type: Simple +data-files: + tcl/clash_namespace.tcl flag cosim description: @@ -86,6 +88,7 @@ library shouldwork/LoadModules exposed-modules: + Clash.Vivado Test.Tasty.Common Test.Tasty.Clash Test.Tasty.Clash.CoreTest @@ -96,11 +99,18 @@ library Test.Tasty.SymbiYosys Test.Tasty.Program Test.Tasty.Verilator + Test.Tasty.Vivado Test.Tasty.Clash.CollectSimResults -- From tests/shouldwork/LoadModules T1796 + other-modules: + Paths_clash_testsuite + + autogen-modules: + Paths_clash_testsuite + build-depends: deepseq, concurrent-extra, diff --git a/tests/src/Clash/Vivado.hs b/tests/src/Clash/Vivado.hs new file mode 100644 index 0000000000..2e698a1d04 --- /dev/null +++ b/tests/src/Clash/Vivado.hs @@ -0,0 +1,149 @@ +{-# LANGUAGE QuasiQuotes #-} + +-- | Generate a TCL script to simulate generated VHDL +-- +-- Run with @vivado -mode batch -source ...@ +module Clash.Vivado ( HdlSource (..), fromModuleName ) where + +import Paths_clash_testsuite (getDataDir) + +import Clash.Driver.Manifest (readManifest, Manifest (..)) +import Clash.Annotations.Primitive (HDL (..)) + +import Data.String.Interpolate (i) +import Data.List (isSuffixOf) + +import System.FilePath (()) +import qualified Data.Text as T + +data HdlSource = HdlSource { directory :: FilePath, buildTarget :: HDL } + +data SimProj = SimProj { vhdlFiles :: [(T.Text, FilePath)] + , verilogFiles :: [(T.Text, FilePath)] + , ipGen :: [FilePath] + } deriving Show + +instance Semigroup SimProj where + (<>) (SimProj vhd0 v0 ip0) (SimProj vhd1 v1 ip1) = + SimProj (vhd0<>vhd1) (v0<>v1) (ip0<>ip1) + +instance Monoid SimProj where + mempty = SimProj [] [] [] + +thread :: [a -> a] -> a -> a +thread = foldr (.) id + +-- | Given something like @topEntity_dcfifo_240A2A9D3FF8D64B.tcl@, return the +-- IP name, @dcfifo@ +parseTcl :: FilePath -> String +parseTcl fp = takeWhile (/= '_') (drop 1 $ dropWhile (/= '_') fp) + +mSimProj :: FilePath -> T.Text -> FilePath -> SimProj -> SimProj +mSimProj dir lib fp p@(SimProj vhd v ip) + | ".vhdl" `isSuffixOf` fp = SimProj ((lib, dir fp):vhd) v ip + | ".vhd" `isSuffixOf` fp = SimProj ((lib, dir fp):vhd) v ip + | ".v" `isSuffixOf` fp = SimProj vhd ((lib, dir fp):v) ip + | ".tcl" `isSuffixOf` fp = SimProj vhd v ((dir fp):ip) + | otherwise = p + +simProjFromClashEntities :: + -- | HDL source dir + FilePath -> + -- | Qualified name + String -> + IO SimProj +simProjFromClashEntities hdlDir qualName = do + (Just mHdl) <- readManifest (hdlDir qualName ++ "/clash-manifest.json") + let deps = T.unpack <$> transitiveDependencies mHdl + nextSimProj <- traverse (simProjFromClashEntities hdlDir) deps + pure $ mconcat nextSimProj <> asSimProj qualName mHdl + +fromModuleName :: + HdlSource -> + -- | Module name + String -> + -- | Entity + String -> + -- | TCL script + IO String +fromModuleName src moduleName entity = do + proj <- simProjFromClashEntities (directory src) (moduleName ++ "." ++ entity) + cabalDir <- getDataDir + pure $ mkTcl cabalDir entity src proj + +asSimProj :: FilePath -> Manifest -> SimProj +asSimProj dir m = + let fps = fst <$> fileNames m + in thread (mSimProj dir (topComponent m) <$> fps) mempty + +mkTcl :: + FilePath -> + -- | Cabal @data@ dir + String -> + -- | Entity + HdlSource -> + SimProj -> + String +mkTcl cabalDir entity hdl (SimProj vhdls vs tcls) = + [i| +source #{cabalDir}/tcl/clash_namespace.tcl + +# create clash namespace +namespace eval clash {} + +set clash::hdl_dir #{hdlDir} + +# for cleanup +file delete -force xilinx_tmp +file mkdir xilinx_tmp +cd xilinx_tmp + +create_project -in_memory + +set clash::ips [list] +|] + + ++ concatMap (\tcl -> + [i|clash::loadTclIface #{parseTcl tcl} ${clash::hdl_dir}/#{tcl}\n|]) tcls + + ++ + [i| + +set clash::ips [clash::runClashScripts] +set clash::ipFiles [get_property IP_FILE [get_ips $clash::ips]] + +read_ip $clash::ipFiles + +generate_target {synthesis simulation} [get_ips $clash::ips] + +foreach modName $clash::ips { + add_files .gen/sources_1/ip/${modName}/synth +} +|] + + ++ readSources + + ++ [i| +update_compile_order -fileset [current_fileset] + +set_property top #{entity} [get_fileset sim_1] + +save_project_as sim -force + +launch_simulation -simset sim_1 -mode behavioral + +run -all + +quit +|] + where + hdlDir = directory hdl + readSources = case buildTarget hdl of + Verilog -> + concatMap (\v -> + [i|read_verilog ${clash::hdl_dir}/#{v}\n|]) (snd <$> vs) + VHDL -> + concatMap (\(lib, vhdl) -> + [i|read_vhdl -library #{lib} ${clash::hdl_dir}/#{vhdl}\n|]) + vhdls + SystemVerilog -> error "SystemVerilog not implemented for Vivado tests" diff --git a/tests/src/Test/Tasty/Clash.hs b/tests/src/Test/Tasty/Clash.hs index 07bf21cd6e..4fc79cb18f 100644 --- a/tests/src/Test/Tasty/Clash.hs +++ b/tests/src/Test/Tasty/Clash.hs @@ -30,6 +30,7 @@ import Test.Tasty.Iverilog import Test.Tasty.Modelsim import Test.Tasty.SymbiYosys import Test.Tasty.Verilator +import Test.Tasty.Vivado {- Note [copy data files hack] @@ -129,6 +130,8 @@ data TestOptions = , verilate :: Verilate -- ^ Whether to run compatible tests through verilator as well as / in -- place of the simulator that would ordinarily be used. + , vivado :: Bool + -- ^ Whether to simulate via Vivado (such as when one depends on Xilinx IP) } allTargets :: [HDL] @@ -149,6 +152,7 @@ instance Default TestOptions where , buildTargets=BuildAuto , vvpStdoutNonEmptyFail=True , verilate=SimAndVerilate + , vivado=False } -- | Directory where testbenches live. @@ -383,6 +387,20 @@ verilatorTests opts@TestOptions{..} tmpDir = (buildTests, simTests) | t <- getBuildTargets opts ] +-- | When we need Xilinx IP +vivadoTests + :: HDL + -> TestOptions + -> IO FilePath + -> String + -> [(TestName, TestTree)] +vivadoTests target opts tmpDir modName = + [ ( "Vivado" + , singleTest "Vivado" (VivadoTest target tmpDir modName t) + ) + | t <- getBuildTargets opts + ] + -- | Generate a test tree for running SymbiYosys sbyTests :: TestOptions -> IO FilePath -> ([(TestName, TestTree)]) sbyTests opts@TestOptions {..} tmpDir = @@ -407,6 +425,10 @@ runTest1 modName opts@TestOptions{..} path target = <> (case verificationTool of Nothing -> [] Just SymbiYosys -> tail $ sequenceTests (show target : path) (clashTest tmpDir : sbyTests opts tmpDir)) + <> if vivado + then + tail (sequenceTests (show target : path) (clashTest tmpDir : vivadoTests target opts tmpDir modName)) + else [] where mkTmpDir = flip createTempDirectory "clash-test" =<< getCanonicalTemporaryDirectory sourceDir = List.foldl' () sourceDirectory (reverse (tail path)) diff --git a/tests/src/Test/Tasty/Program.hs b/tests/src/Test/Tasty/Program.hs index 62f4adbf0c..a7fcc6d4cf 100644 --- a/tests/src/Test/Tasty/Program.hs +++ b/tests/src/Test/Tasty/Program.hs @@ -94,6 +94,7 @@ data ExpectOutput a | ExpectStdErr a | ExpectEither a | ExpectNotStdErr a + | ExpectNotStdOut a | ExpectNothing deriving Functor @@ -356,6 +357,8 @@ runFailingProgram testExitCode program args stdO errOnEmptyStderr expectedCode e unexpectedStd "stdout or stderr" program args code stderrT stdoutT r ExpectNotStdErr r | cleanNewlines r `T.isInfixOf` cleanNewlines stderrT -> unexpectedNonEmptyStderr program args code stderrT stdoutT + ExpectNotStdOut r | cleanNewlines r `T.isInfixOf` cleanNewlines stdoutT -> + unexpectedNonEmptyStdout program args code stderrT stdoutT _ -> if testExitCode then case expectedCode of diff --git a/tests/src/Test/Tasty/Vivado.hs b/tests/src/Test/Tasty/Vivado.hs new file mode 100644 index 0000000000..2550df2924 --- /dev/null +++ b/tests/src/Test/Tasty/Vivado.hs @@ -0,0 +1,53 @@ +{-# LANGUAGE TypeApplications #-} + +module Test.Tasty.Vivado where + +import Data.Coerce (coerce) +import Data.Tagged (Tagged (..)) +import Data.Proxy (Proxy (..)) +import System.IO (hPutStr, hFlush) + +import System.IO.Temp (withSystemTempFile) +import Test.Tasty.Providers (IsTest (..), testPassed) +import Test.Tasty.Options (IsOption (..), safeReadBool, flagCLParser, lookupOption, OptionDescription (..)) + +import Clash.Vivado (fromModuleName, HdlSource (..)) +import Clash.Annotations.Primitive (HDL (..)) +import Test.Tasty.Program + +-- | @--vivado@ flag for enabling tests that use vivado. +newtype Vivado = Vivado Bool + +instance IsOption Vivado where + defaultValue = Vivado True + parseValue = fmap Vivado . safeReadBool + optionName = pure "no-vivado" + optionHelp = pure "Skip Vivado tests" + optionCLParser = flagCLParser Nothing (Vivado False) + +data VivadoTest = VivadoTest + { hdlTarget :: HDL + , hdlSource :: IO FilePath + , moduleTest :: String + , entity :: String + } + +instance IsTest VivadoTest where + run optionSet (VivadoTest target dir m top) progressCallback + | Vivado True <- lookupOption optionSet = + withSystemTempFile "sim.tcl" $ \fp h -> do + hdlSrc <- dir + tcl <- fromModuleName (HdlSource hdlSrc target) m top + hPutStr h tcl *> + hFlush h + runVivado hdlSrc ["-mode", "batch", "-source", fp] + | otherwise = pure (testPassed "Ignoring test due to --no-vivado") + + where + vivado workDir args = + TestFailingProgram True "vivado" args NoGlob PrintNeither False (Just 0) (ExpectNotStdOut "expected: ") (Just workDir) + runVivado workDir args = + run optionSet (vivado workDir args) progressCallback + + testOptions = + coerce (coerce (testOptions @TestProgram) <> [Option (Proxy @Vivado)]) diff --git a/tests/tcl/clash_namespace.tcl b/tests/tcl/clash_namespace.tcl new file mode 100644 index 0000000000..34a187195b --- /dev/null +++ b/tests/tcl/clash_namespace.tcl @@ -0,0 +1,31 @@ +namespace eval clash { + # Populate a namespace with a Clash-generated Tcl interface. + # Namespace is clash::tclIface::$top::$baseName + proc loadTclIface {top clashTclFile} { + # Evaluate script code inside temporary throwaway namespace to + # separate its definitions from ours and reduce the chance of + # accidentally corrupting our code. + namespace eval tmp "source $clashTclFile" + set baseName [file rootname [file tail $clashTclFile]] + tmp::createNamespace [namespace current]::tclIface::${top}::${baseName} + namespace delete tmp + } + + proc runClashScripts {} { + # Identical names means identical IP, only one run needed even if it + # occurs in multiple HDL directories. + set seen [list] + foreach topNs [namespace children tclIface] { + foreach tclIface [namespace children $topNs] { + set api [subst $${tclIface}::api] + set ipName [subst $${tclIface}::ipName] + if {$ipName in $seen} { + continue + } + ${tclIface}::createIp + lappend seen $ipName + } + } + return $seen + } +}