Skip to content

Commit

Permalink
Check whether we can recover from reset deassertion
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Feb 14, 2025
1 parent 01f56d4 commit 5011bd3
Show file tree
Hide file tree
Showing 2 changed files with 46 additions and 2 deletions.
4 changes: 2 additions & 2 deletions clash-vexriscv-sim/app/VexRiscvChainSimulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Clash.Prelude
import Control.Monad (forM_, when)
import GHC.Char (chr)
import GHC.IO.Handle (Handle, hFlush, hPutStr)
import Options.Applicative (Parser, execParser, fullDesc, header, help, helper, info, long, progDesc, short, strOption, option, auto)
import Options.Applicative (Parser, auto, execParser, fullDesc, header, help, helper, info, long, option, progDesc, short, strOption)
import Protocols.Wishbone
import System.Exit (exitFailure)
import System.IO (IOMode (WriteMode), hPutChar, hPutStrLn, openFile, stdout)
Expand Down Expand Up @@ -101,7 +101,7 @@ type CpuSignals =
, WishboneS2M (BitVector 32)
)

toReset :: KnownDomain dom => Maybe Int -> Reset dom
toReset :: (KnownDomain dom) => Maybe Int -> Reset dom
toReset Nothing = resetGenN d2
toReset (Just n) = unsafeFromActiveHigh $ fromList (L.replicate n True <> L.repeat False)

Expand Down
44 changes: 44 additions & 0 deletions clash-vexriscv-sim/tests/Tests/JtagChain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,49 @@ testInResetA debug = do
gdbBExitCode <- waitForProcess gdbProcHandleB
ExitSuccess @=? gdbBExitCode

testResetDeassertion ::
(HasCallStack) =>
-- | Print debug output of subprocesses
Bool ->
Assertion
testResetDeassertion debug = do
Args{vexRiscvProc, openOcdProc, gdbProcB, gdbProcA, logPathA, logPathB} <- createArgs

let
-- Timeout after 60 seconds. Warning: removing the type signature breaks
-- stack traces.
expectLine :: (HasCallStack) => Bool -> Handle -> String -> Assertion
expectLine = expectLineOrTimeout 60_000_000

waitForLine :: (HasCallStack) => Bool -> Handle -> String -> Assertion
waitForLine = waitForLineOrTimeout 60_000_000

let vexRiscvProc1 = addArgs vexRiscvProc ["--keep-cpu-a-in-reset", show @Int 50_000]

withStreamingFiles (logPathA :> logPathB :> Nil) $ \(vecToTuple -> (logA, logB)) -> do
withCreateProcess vexRiscvProc1 $ \_ (fromJust -> simStdOut) _ _ -> do
waitForLine debug simStdOut "JTAG bridge ready at port 7894"

expectLine debug logB "[CPU] b" -- first load
withCreateProcess openOcdProc $ \_ _ (fromJust -> openOcdStdErr) _ -> do
waitForLine debug openOcdStdErr "Error: [riscv.cpu0] Examination failed"
waitForLine debug openOcdStdErr "[riscv.cpu1] Target successfully examined."
waitForLine debug openOcdStdErr "Halting processor"

withCreateProcess gdbProcB $ \_ _ _ gdbProcHandleB -> do
waitForLine debug openOcdStdErr "[riscv.cpu0] Target successfully examined."

withCreateProcess gdbProcA $ \_ _ _ gdbProcHandleA -> do
expectLine debug logA "[CPU] a" -- first load
expectLine debug logA "[CPU] a" -- breakpoint
expectLine debug logA "[CPU] b" -- new binary loaded
expectLine debug logB "[CPU] b" -- breakpoint
expectLine debug logB "[CPU] a" -- new binary loaded
gdbAExitCode <- waitForProcess gdbProcHandleA
gdbBExitCode <- waitForProcess gdbProcHandleB
ExitSuccess @=? gdbAExitCode
ExitSuccess @=? gdbBExitCode

ensureExists :: (HasCallStack) => FilePath -> IO ()
ensureExists path = unlessM (doesPathExist path) (withFile path WriteMode (\_ -> pure ()))

Expand All @@ -208,6 +251,7 @@ tests = askOption $ \(JtagDebug debug) ->
"JTAG chaining"
[ testCase "Basic GDB commands, breakpoints, and program loading" (testBoth debug)
, testCase "Program loading with CPU A held in reset" (testInResetA debug)
, testCase "CPU A should recover after reset deassertion" (testResetDeassertion debug)
]

main :: IO ()
Expand Down

0 comments on commit 5011bd3

Please sign in to comment.