Skip to content

Commit

Permalink
Expose JTAG output port, and move debug config into a standalone file.
Browse files Browse the repository at this point in the history
  • Loading branch information
rslawson committed Nov 24, 2024
1 parent 0ac4a4f commit 72904a3
Show file tree
Hide file tree
Showing 5 changed files with 65 additions and 52 deletions.
48 changes: 12 additions & 36 deletions clash-vexriscv-sim/app/VexRiscvSimulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE GADTs #-}

{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-}

Expand All @@ -21,36 +20,11 @@ import System.Environment (getArgs)
import System.IO (putChar, hFlush, stdout)
import Text.Printf (printf)


import Utils.ProgramLoad (loadProgramDmem)
import Utils.DebugConfig (DebugConfiguration (..))
import Utils.Cpu (cpu)
import Utils.ProgramLoad (loadProgramDmem)
import System.Exit (exitFailure)

--------------------------------------
--
-- Debugging configuration
--
--------------------------------------

data DebugConfiguration where
-- | Run a program and only output what the program writes to the
-- character-device
RunCharacterDevice :: DebugConfiguration
-- | Run a program and print detailed information of CPU bus interactions
InspectBusses ::
-- | # of cycles the program takes to initialise the instruction memory
Int ->
-- | # of "uninteresting" cycles to skip, such as runtime setup code
Int ->
-- | # of "interesting" cycles to inspect
Maybe Int ->
-- | inspect instruct-bus interactions
Bool ->
-- | inspect data-bus interactions
Bool ->
DebugConfiguration
-- | Run a program and output all the write operations
InspectWrites :: DebugConfiguration
import VexRiscv.JtagTcpBridge (vexrJtagBridge)

-- change this variable to the configuration you want to use

Expand Down Expand Up @@ -80,16 +54,18 @@ main = do
withClockResetEnable @System clockGen resetGen enableGen $
loadProgramDmem @System elfFile

let cpuOut@(unbundle -> (_circuit, writes, _iBus, _dBus)) =
withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
let (circ, writes1, iBus, dBus) = cpu (Just 7894) iMem dMem
dBus' = register emptyWishboneS2M dBus
in bundle (circ, writes1, iBus, dBus')
let
jtagPort = vexrJtagBridge 7894 jtagOut
cpuOut@(unbundle -> (_circuit, jtagOut, writes, _iBus, _dBus)) =
withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
let (circ, jto, writes1, iBus, dBus) = cpu (Just jtagPort) iMem dMem
dBus' = register emptyWishboneS2M dBus
in bundle (circ, jto, writes1, iBus, dBus')

case debugConfig of
RunCharacterDevice ->
forM_ (sample_lazy @System (bundle (register @System (unpack 0) cpuOut, cpuOut))) $
\((_out, write, dS2M, iS2M), (out1, _write, _dS2M, _iS2M)) -> do
\((_out, _, write, dS2M, iS2M), (out1, _, _write, _dS2M, _iS2M)) -> do

when (err dS2M) $ do
let dBusM2S = dBusWbM2S out1
Expand Down Expand Up @@ -122,7 +98,7 @@ main = do
let total = initCycles + uninteresting + nInteresting in
L.zip [0 ..] $ L.take total $ sample_lazy @System cpuOut

forM_ sampled $ \(i, (out, _, iBusS2M, dBusS2M)) -> do
forM_ sampled $ \(i, (out, _, _, iBusS2M, dBusS2M)) -> do
let
doPrint = i >= skipTotal

Expand Down
1 change: 1 addition & 0 deletions clash-vexriscv-sim/clash-vexriscv-sim.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ library
default-language: Haskell2010
exposed-modules:
Utils.Cpu
Utils.DebugConfig
Utils.Instance
Utils.Interconnect
Utils.ProgramLoad
Expand Down
31 changes: 16 additions & 15 deletions clash-vexriscv-sim/src/Utils/Cpu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import GHC.Stack (HasCallStack)
import Utils.ProgramLoad (Memory, DMemory)
import Utils.Interconnect (interconnectTwo)
import Clash.Explicit.Prelude (unsafeOrReset)
import Data.Maybe (fromMaybe)

createDomain vXilinxSystem{vName="Basic50", vPeriod= hzToPeriod 50_000_000}

Expand All @@ -39,33 +40,33 @@ cpu ::
-- convenient it is to use this within a design with synchronous resets.
-- , HasAsynchronousReset dom
) =>
Maybe Integer ->
Maybe (Signal dom JtagIn) ->
DMemory dom ->
DMemory dom ->
( Signal dom CpuOut,
-- writes
Signal dom (Maybe (BitVector 32, BitVector 32)),
-- iBus responses
Signal dom (WishboneS2M (BitVector 32)),
-- dBus responses
( Signal dom CpuOut
, Signal dom JtagOut
, -- writes
Signal dom (Maybe (BitVector 32, BitVector 32))
, -- iBus responses
Signal dom (WishboneS2M (BitVector 32))
, -- dBus responses
Signal dom (WishboneS2M (BitVector 32))
)
cpu jtagPort bootIMem bootDMem =
( output
cpu jtagIn0 bootIMem bootDMem =
( cpuOut
, jtagOut
, writes
, iS2M
, dS2M
)
where
(output, jtagOut) = vexRiscv hasClock (hasReset `unsafeOrReset` jtagReset) input jtagIn
(cpuOut, jtagOut) = vexRiscv hasClock (hasReset `unsafeOrReset` jtagReset) input jtagIn1

jtagReset =
unsafeFromActiveHigh $ register False $
bitToBool . debugReset <$> jtagOut

jtagIn = case jtagPort of
Just port -> vexrJtagBridge (fromInteger port) jtagOut
Nothing -> pure JTag.defaultIn
jtagIn1 = fromMaybe (pure JTag.defaultIn) jtagIn0

{-
00000000 - dummy area
Expand All @@ -75,15 +76,15 @@ cpu jtagPort bootIMem bootDMem =

-- The I-bus is only split once, for the D-mem and everything below.
(iS2M, vecToTuple . unbundle -> (iMemIM2S, dMemIM2S)) = interconnectTwo
(unBusAddr . iBusWbM2S <$> output)
(unBusAddr . iBusWbM2S <$> cpuOut)
((0x0000_0000, iMemIS2M) :> (0x4000_0000, dMemIS2M) :> Nil)

-- Because the dummy region should never be accessed by the instruction bus
-- it's just "ignored"
(iMemIS2M, iMemDS2M) = bootIMem (mapAddr (\x -> complement 0x2000_0000 .&. x) <$> iMemIM2S) iMemDM2S

-- needed for 'writes' below
dM2S = dBusWbM2S <$> output
dM2S = dBusWbM2S <$> cpuOut

-- because of the memory map having the dummy at 0x0.., then instructions
-- and then data memory, the D-bus is split in an "upper" and "lower" region,
Expand Down
34 changes: 34 additions & 0 deletions clash-vexriscv-sim/src/Utils/DebugConfig.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
-- SPDX-FileCopyrightText: 2022-2024 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE GADTs #-}

module Utils.DebugConfig where

import Prelude

--------------------------------------
--
-- Debugging configuration
--
--------------------------------------

data DebugConfiguration where
-- | Run a program and only output what the program writes to the
-- character-device
RunCharacterDevice :: DebugConfiguration
-- | Run a program and print detailed information of CPU bus interactions
InspectBusses ::
-- | # of cycles the program takes to initialise the instruction memory
Int ->
-- | # of "uninteresting" cycles to skip, such as runtime setup code
Int ->
-- | # of "interesting" cycles to inspect
Maybe Int ->
-- | inspect instruct-bus interactions
Bool ->
-- | inspect data-bus interactions
Bool ->
DebugConfiguration
-- | Run a program and output all the write operations
InspectWrites :: DebugConfiguration
3 changes: 2 additions & 1 deletion clash-vexriscv-sim/tests/tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ runProgramExpect act n expected = withSystemTempFile "ELF" $ \fp _ -> do
(iMem, dMem) <- withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
loadProgramDmem fp

let _all@(unbundle -> (_circuit, writes, _iBus, _dBus)) =
let _all@(unbundle -> (_circuit, _, writes, _iBus, _dBus)) =
withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
bundle (cpu Nothing iMem dMem)

Expand All @@ -60,6 +60,7 @@ findTests ::
IO [(String, FilePath, FilePath)]
-- test name bin path expected-path
findTests srcDir binDir = do

srcFiles <- listDirectory srcDir

let expectFiles = L.filter (\p -> takeExtension p == ".expected") srcFiles
Expand Down

0 comments on commit 72904a3

Please sign in to comment.