Skip to content

Commit

Permalink
Merge pull request #695 from bittide/add-vcd-tracing-to-vexriscv
Browse files Browse the repository at this point in the history
 Bump `clash-vexriscv` for VCD support
  • Loading branch information
martijnbastiaan authored Dec 4, 2024
2 parents bdaf6bd + 67bc71e commit c92c648
Show file tree
Hide file tree
Showing 35 changed files with 895 additions and 138 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ fullMeshRiscvCopyTest clk rst callistoResult dataCounts = unbundle fIncDec
toSignals
( circuit $ \jtag -> do
[wbFincFdec, wbClockControl, wbDebug] <-
withClockResetEnable clk rst enableGen $ processingElement @dom peConfig -< jtag
withClockResetEnable clk rst enableGen $ processingElement @dom NoDumpVcd peConfig -< jtag
fIncDecCallisto -< wbFincFdec
[ccd0, ccd1] <-
csDupe
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,7 @@ fullMeshRiscvTest clk rst dataCounts = unbundle fIncDec
toSignals
( circuit $ \jtag -> do
[wbClockControl, wbDebug, wbDummy] <-
withClockResetEnable clk rst enableGen $ processingElement @dom peConfig -< jtag
withClockResetEnable clk rst enableGen $ processingElement @dom NoDumpVcd peConfig -< jtag
idleSink -< wbDummy
[ccd0, ccd1] <-
csDupe
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -245,7 +245,7 @@ riscvCopyTest clk rst mask callistoResult dataCounts = unbundle fIncDec
toSignals
( circuit $ \jtag -> do
[wbFincFdec, wbClockControl, wbDebug] <-
withClockResetEnable clk rst enableGen $ processingElement @dom peConfig -< jtag
withClockResetEnable clk rst enableGen $ processingElement @dom NoDumpVcd peConfig -< jtag
fIncDecCallisto -< wbFincFdec
[ccd0, ccd1] <-
csDupe
Expand Down
2 changes: 1 addition & 1 deletion bittide-instances/src/Bittide/Instances/Hitl/VexRiscv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ vexRiscvInner jtagIn0 uartRx =
circuitFn ((uartRx, jtagIn0), (pure (), pure ()))

Circuit circuitFn = circuit $ \(uartRx, jtag) -> do
[timeBus, uartBus, statusRegisterBus] <- processingElement peConfig -< jtag
[timeBus, uartBus, statusRegisterBus] <- processingElement NoDumpVcd peConfig -< jtag
(uartTx, _uartStatus) <-
uartInterfaceWb @dom d16 d16 (uartDf $ SNat @921600) -< (uartBus, uartRx)
timeWb -< timeBus
Expand Down
2 changes: 1 addition & 1 deletion bittide-instances/src/Bittide/Instances/Pnr/Ethernet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ vexRiscGmii SNat sysClk sysRst rxClk rxRst txClk txRst fwd =
rxClkEna
macStatIf = wcre $ macStatusInterfaceWb d16
uart = wcre $ uartInterfaceWb d32 d2 (uartDf baud)
pe = wcre processingElement peConfig
pe = wcre processingElement NoDumpVcd peConfig
wbToAxiTx' = wcre wbToAxiTx
wbAxiRxBuffer = wcre wbAxisRxBufferCircuit (SNat @2048)
axiTxPipe = wcre (axiUserMapC (const False) <| axiStreamToByteStream)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ vexRiscUartHello diffClk rst_in =
$ withClockResetEnable clk200 rst200 enableGen
$ circuit
$ \(uartRx, jtag) -> do
[uartBus, timeBus] <- processingElement @Basic200 peConfig -< jtag
[uartBus, timeBus] <- processingElement @Basic200 NoDumpVcd peConfig -< jtag
(uartTx, _uartStatus) <-
uartInterfaceWb d16 d16 (uartDf $ SNat @921600) -< (uartBus, uartRx)
timeWb -< timeBus
Expand Down
3 changes: 2 additions & 1 deletion bittide-instances/tests/Tests/ClockControlWb.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Test.Tasty.HUnit
import Test.Tasty.TH
import Text.Parsec
import Text.Parsec.String
import VexRiscv (DumpVcd (NoDumpVcd))

-- internal imports
import Bittide.Arithmetic.Time (PeriodToCycles)
Expand Down Expand Up @@ -135,7 +136,7 @@ dut =
$ circuit
$ \_unit -> do
(uartRx, jtag) <- idleSource -< ()
[uartBus, ccWb, dbgWb] <- processingElement peConfig -< jtag
[uartBus, ccWb, dbgWb] <- processingElement NoDumpVcd peConfig -< jtag
(uartTx, _uartStatus) <- uartInterfaceWb d2 d2 uartSim -< (uartBus, uartRx)
[ccd0, ccd1] <-
csDupe
Expand Down
3 changes: 2 additions & 1 deletion bittide-instances/tests/Wishbone/Axi.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ import Test.Tasty.HUnit
import Test.Tasty.TH
import Text.Parsec
import Text.Parsec.String
import VexRiscv (DumpVcd (NoDumpVcd))

-- Qualified
import qualified Protocols.Df as Df
Expand Down Expand Up @@ -67,7 +68,7 @@ dut =
$ circuit
$ \_unit -> do
(uartTx, jtag) <- idleSource -< ()
[uartBus, axiTxBus, wbNull, axiRxBus] <- processingElement peConfig -< jtag
[uartBus, axiTxBus, wbNull, axiRxBus] <- processingElement NoDumpVcd peConfig -< jtag
wbAlwaysAck -< wbNull
(uartRx, _uartStatus) <- uartInterfaceWb d2 d2 uartSim -< (uartBus, uartTx)
_interrupts <- wbAxisRxBufferCircuit (SNat @128) -< (axiRxBus, axiStream)
Expand Down
3 changes: 2 additions & 1 deletion bittide-instances/tests/Wishbone/CaptureUgn.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ import System.FilePath
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import VexRiscv (DumpVcd (NoDumpVcd))

import Bittide.CaptureUgn
import Bittide.DoubleBufferedRam
Expand Down Expand Up @@ -92,7 +93,7 @@ dut ::
dut eb localCounter = circuit $ \uartRx -> do
eb <- ebCircuit -< ()
jtagIdle <- idleSource -< ()
[uartBus, ugnBus] <- processingElement @dom peConfig -< jtagIdle
[uartBus, ugnBus] <- processingElement @dom NoDumpVcd peConfig -< jtagIdle
(uartTx, _uartStatus) <- uartInterfaceWb d2 d2 uartSim -< (uartBus, uartRx)
_bittideData <- captureUgn localCounter -< (ugnBus, eb)
idC -< uartTx
Expand Down
3 changes: 2 additions & 1 deletion bittide-instances/tests/Wishbone/DnaPortE2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ import System.FilePath
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import VexRiscv (DumpVcd (NoDumpVcd))

import Bittide.DoubleBufferedRam
import Bittide.ProcessingElement
Expand Down Expand Up @@ -56,7 +57,7 @@ dut ::
Circuit (Df dom (BitVector 8)) (Df dom (BitVector 8))
dut = circuit $ \uartRx -> do
jtag <- idleSource -< ()
[uartBus, dnaWb] <- processingElement @dom peConfig -< jtag
[uartBus, dnaWb] <- processingElement @dom NoDumpVcd peConfig -< jtag
(uartTx, _uartStatus) <- uartInterfaceWb d2 d2 uartSim -< (uartBus, uartRx)
readDnaPortE2Wb simDna2 -< dnaWb
idC -< uartTx
Expand Down
3 changes: 2 additions & 1 deletion bittide-instances/tests/Wishbone/Time.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ import Test.Tasty.HUnit
import Test.Tasty.TH
import Text.Parsec
import Text.Parsec.String
import VexRiscv (DumpVcd (NoDumpVcd))

-- Qualified
import qualified Protocols.Df as Df
Expand Down Expand Up @@ -67,7 +68,7 @@ dut = withClockResetEnable clockGen resetGen enableGen
$ circuit
$ \_unit -> do
(uartRx, jtag) <- idleSource -< ()
[uartBus, timeBus] <- processingElement peConfig -< jtag
[uartBus, timeBus] <- processingElement NoDumpVcd peConfig -< jtag
(uartTx, _uartStatus) <- uartInterfaceWb d2 d2 uartSim -< (uartBus, uartRx)
timeWb -< timeBus
idC -< uartTx
Expand Down
49 changes: 28 additions & 21 deletions bittide/src/Bittide/Node.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,9 @@ vector of ever increasing base addresses (increments of 0x1000).
simpleNodeConfig :: NodeConfig 1 2
simpleNodeConfig =
NodeConfig
(ManagementConfig (ScatterConfig sgConfig) (GatherConfig sgConfig) nmuConfig)
(ManagementConfig (ScatterConfig sgConfig) (GatherConfig sgConfig) nmuConfig NoDumpVcd)
switchCal
(repeat (GppeConfig (ScatterConfig sgConfig) (GatherConfig sgConfig) peConfig))
(repeat (GppeConfig (ScatterConfig sgConfig) (GatherConfig sgConfig) peConfig NoDumpVcd))
where
switchCal = CalendarConfig (SNat @1024) (switchEntry :> Nil) (switchEntry :> Nil)
sgConfig = CalendarConfig (SNat @1024) (sgEntry :> Nil) (sgEntry :> Nil)
Expand Down Expand Up @@ -104,6 +104,7 @@ data ManagementConfig nodeBusses where
ScatterConfig 4 (NmuRemBusWidth nodeBusses) ->
GatherConfig 4 (NmuRemBusWidth nodeBusses) ->
PeConfig (nodeBusses + NmuInternalBusses) ->
DumpVcd ->
ManagementConfig nodeBusses

{- | Configuration for a general purpose processing element together with its link to the
Expand All @@ -117,6 +118,7 @@ data GppeConfig nmuRemBusWidth where
-- has four external busses connected to the instruction memory, data memory
-- , 'scatterUnitWb' and 'gatherUnitWb'.
PeConfig 4 ->
DumpVcd ->
GppeConfig nmuRemBusWidth

{-# NOINLINE gppe #-}
Expand Down Expand Up @@ -148,14 +150,18 @@ gppe ::
( Signal dom (DataLink 64)
, Vec 2 (Signal dom (WishboneS2M (Bytes 4)))
)
gppe (GppeConfig scatterConfig gatherConfig peConfig, linkIn, vecToTuple -> (nmuM2S0, nmuM2S1)) =
(linkOut, nmuS2M0 :> nmuS2M1 :> Nil)
where
(suS2M, nmuS2M0) = scatterUnitWb scatterConfig nmuM2S0 linkIn suM2S
(linkOut, guS2M, nmuS2M1) = gatherUnitWb gatherConfig nmuM2S1 guM2S
(_, wbM2Ss) = toSignals (processingElement peConfig) (pure $ JtagIn low low low, wbS2Ms)
(suM2S, guM2S) = vecToTuple wbM2Ss
wbS2Ms = suS2M :> guS2M :> Nil
gppe
( GppeConfig scatterConfig gatherConfig peConfig dumpVcd
, linkIn
, vecToTuple -> (nmuM2S0, nmuM2S1)
) =
(linkOut, nmuS2M0 :> nmuS2M1 :> Nil)
where
(suS2M, nmuS2M0) = scatterUnitWb scatterConfig nmuM2S0 linkIn suM2S
(linkOut, guS2M, nmuS2M1) = gatherUnitWb gatherConfig nmuM2S1 guM2S
(_, wbM2Ss) = toSignals (processingElement dumpVcd peConfig) (pure $ JtagIn low low low, wbS2Ms)
(suM2S, guM2S) = vecToTuple wbM2Ss
wbS2Ms = suS2M :> guS2M :> Nil

{-# NOINLINE managementUnit #-}

Expand All @@ -170,13 +176,14 @@ gppeC ::
Circuit
(CSignal dom (DataLink 64), Vec 2 (Wishbone dom 'Standard nmuRemBusWidth (Bytes 4)))
(CSignal dom (DataLink 64))
gppeC (GppeConfig scatterConfig gatherConfig peConfig) = circuit $ \(linkIn, nmuWbs) -> do
[wbScatCal, wbGathCal] <- idC -< nmuWbs
jtag <- idleSource -< ()
[wbScat, wbGu] <- processingElement peConfig -< jtag
linkOut <- gatherUnitWbC gatherConfig -< (wbGu, wbGathCal)
scatterUnitWbC scatterConfig -< (linkIn, wbScat, wbScatCal)
idC -< linkOut
gppeC (GppeConfig scatterConfig gatherConfig peConfig dumpVcd) =
circuit $ \(linkIn, nmuWbs) -> do
[wbScatCal, wbGathCal] <- idC -< nmuWbs
jtag <- idleSource -< ()
[wbScat, wbGu] <- processingElement dumpVcd peConfig -< jtag
linkOut <- gatherUnitWbC gatherConfig -< (wbGu, wbGathCal)
scatterUnitWbC scatterConfig -< (linkIn, wbScat, wbScatCal)
idC -< linkOut

{- | A special purpose 'processingElement' that manages a Bittide Node. It contains
a 'processingElement', 'linkToPe' and 'peToLink' which create the interface for the
Expand All @@ -202,14 +209,14 @@ managementUnit ::
( Signal dom (DataLink 64)
, Vec nodeBusses (Signal dom (WishboneM2S (NmuRemBusWidth nodeBusses) 4 (Bytes 4)))
)
managementUnit (ManagementConfig scatterConfig gatherConfig peConfig) linkIn nodeS2Ms =
managementUnit (ManagementConfig scatterConfig gatherConfig peConfig dumpVcd) linkIn nodeS2Ms =
(linkOut, nodeM2Ss)
where
(suS2M, nmuS2M0) = scatterUnitWb scatterConfig nmuM2S0 linkIn suM2S
(linkOut, guS2M, nmuS2M1) = gatherUnitWb gatherConfig nmuM2S1 guM2S
(vecToTuple -> (suM2S, guM2S), rest) = splitAtI nmuM2Ss
(vecToTuple -> (nmuM2S0, nmuM2S1), nodeM2Ss) = splitAtI rest
(_, nmuM2Ss) = toSignals (processingElement peConfig) (pure $ JtagIn low low low, nmuS2Ms)
(_, nmuM2Ss) = toSignals (processingElement dumpVcd peConfig) (pure $ JtagIn low low low, nmuS2Ms)
nmuS2Ms = suS2M :> guS2M :> nmuS2M0 :> nmuS2M1 :> nodeS2Ms

managementUnitC ::
Expand All @@ -228,9 +235,9 @@ managementUnitC ::
( CSignal dom (DataLink 64)
, Vec nodeBusses (Wishbone dom 'Standard (NmuRemBusWidth nodeBusses) (Bytes 4))
)
managementUnitC (ManagementConfig scatterConfig gatherConfig peConfig) = circuit $ \linkIn -> do
managementUnitC (ManagementConfig scatterConfig gatherConfig peConfig dumpVcd) = circuit $ \linkIn -> do
jtag <- idleSource -< ()
peWbs <- processingElement peConfig -< jtag
peWbs <- processingElement dumpVcd peConfig -< jtag
([wbScatCal, wbScat, wbGathCal, wbGu], nmuWbs) <- splitAtC d4 -< peWbs
linkOut <- gatherUnitWbC gatherConfig -< (wbGu, wbGathCal)
scatterUnitWbC scatterConfig -< (linkIn, wbScat, wbScatCal)
Expand Down
12 changes: 7 additions & 5 deletions bittide/src/Bittide/ProcessingElement.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Clash.Prelude

import Protocols
import Protocols.Wishbone
import VexRiscv (CpuIn (..), CpuOut (..), Jtag, JtagOut (debugReset), vexRiscv)
import VexRiscv (CpuIn (..), CpuOut (..), DumpVcd, Jtag, JtagOut (debugReset), vexRiscv)

import Bittide.DoubleBufferedRam
import Bittide.Extra.Maybe
Expand Down Expand Up @@ -50,12 +50,13 @@ data PeConfig nBusses where
processingElement ::
forall dom nBusses.
(HiddenClockResetEnable dom) =>
DumpVcd ->
PeConfig nBusses ->
Circuit
(Jtag dom)
(Vec (nBusses - 2) (Wishbone dom 'Standard (MappedBusAddrWidth 30 nBusses) (Bytes 4)))
processingElement (PeConfig memMapConfig initI initD) = circuit $ \jtagIn -> do
(iBus0, dBus0) <- rvCircuit (pure low) (pure low) (pure low) -< jtagIn
processingElement dumpVcd (PeConfig memMapConfig initI initD) = circuit $ \jtagIn -> do
(iBus0, dBus0) <- rvCircuit dumpVcd (pure low) (pure low) (pure low) -< jtagIn
iBus1 <-
ilaWb (SSymbol @"instructionBus") 2 D4096 onTransactionWb onTransactionWb -< iBus0
dBus1 <- ilaWb (SSymbol @"dataBus") 2 D4096 onTransactionWb onTransactionWb -< dBus0
Expand Down Expand Up @@ -89,6 +90,7 @@ splitAtC SNat = Circuit go

rvCircuit ::
(HiddenClockResetEnable dom) =>
DumpVcd ->
Signal dom Bit ->
Signal dom Bit ->
Signal dom Bit ->
Expand All @@ -97,13 +99,13 @@ rvCircuit ::
( Wishbone dom 'Standard 30 (Bytes 4)
, Wishbone dom 'Standard 30 (Bytes 4)
)
rvCircuit tInterrupt sInterrupt eInterrupt = Circuit go
rvCircuit dumpVcd tInterrupt sInterrupt eInterrupt = Circuit go
where
go (jtagIn, (iBusIn, dBusIn)) = (jtagOut, (iBusWbM2S <$> cpuOut, dBusWbM2S <$> cpuOut))
where
tupToCoreIn (timerInterrupt, softwareInterrupt, externalInterrupt, iBusWbS2M, dBusWbS2M) = CpuIn{..}
rvIn = tupToCoreIn <$> bundle (tInterrupt, sInterrupt, eInterrupt, iBusIn, dBusIn)
(cpuOut, jtagOut) = vexRiscv hasClock (hasReset `unsafeOrReset` jtagReset) rvIn jtagIn
(cpuOut, jtagOut) = vexRiscv dumpVcd hasClock (hasReset `unsafeOrReset` jtagReset) rvIn jtagIn
jtagReset = unsafeFromActiveHigh (delay False (bitToBool . debugReset <$> jtagOut))

-- | Map a function over the address field of 'WishboneM2S'
Expand Down
3 changes: 2 additions & 1 deletion clash-vexriscv/.github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,8 @@ jobs:
- name: Run `clash-vexriscv-sim` unittests
run: |
cabal run clash-vexriscv-sim:unittests -- -j2
# Can't run the unit tests with multiple threads because of the common use of port 7894.
cabal run clash-vexriscv-sim:unittests -- -j1
- name: Run `clash-vexriscv-sim` HDL test
run: |
Expand Down
9 changes: 8 additions & 1 deletion clash-vexriscv/cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,14 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/clash-lang/clash-protocols.git
tag: eb76cd1be746ae91beff60c0f16d8c1dd888662c
tag: 0832a422e77422739401896f6612620d17baa289
subdir: clash-protocols

source-repository-package
type: git
location: https://github.com/clash-lang/clash-protocols.git
tag: 0832a422e77422739401896f6612620d17baa289
subdir: clash-protocols-base

source-repository-package
type: git
Expand Down
2 changes: 1 addition & 1 deletion clash-vexriscv/clash-vexriscv-sim/app/HdlTest.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
-- SPDX-FileCopyrightText: 2023 Google LLC
-- SPDX-FileCopyrightText: 2023-2024 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0

Expand Down
Loading

0 comments on commit c92c648

Please sign in to comment.