Skip to content

Commit

Permalink
add JTAG support to the core
Browse files Browse the repository at this point in the history
Co-Authored-By: Martijn Bastiaan <[email protected]>
  • Loading branch information
hydrolarus and martijnbastiaan committed Mar 6, 2024
1 parent 6a0805f commit d4ded17
Show file tree
Hide file tree
Showing 31 changed files with 2,692 additions and 316 deletions.
3 changes: 3 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -65,3 +65,6 @@ log
vivado_*
tight_setup_hold_pins.txt
.Xil

# Verilator debug output
simulation_dump.vcd
10 changes: 10 additions & 0 deletions Cargo.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions Cargo.toml
Original file line number Diff line number Diff line change
Expand Up @@ -13,5 +13,6 @@ opt-level = "z"
[workspace]
members = [
"clash-vexriscv-sim/test-programs",
"debug-test",
]
resolver = "2"
1 change: 0 additions & 1 deletion cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ packages:
clash-vexriscv-sim/

write-ghc-environment-files: always

tests: True


Expand Down
11 changes: 7 additions & 4 deletions clash-vexriscv-sim/app/HdlTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,13 @@ import VexRiscv
circuit ::
"CLK" ::: Clock System ->
"RST" ::: Reset System ->
"INPUT" ::: Signal System Input ->
"OUTPUT" ::: Signal System Output
circuit clk rst input =
withClockResetEnable clk rst enableGen vexRiscv input
"CPU_COMB_INPUT" ::: Signal System CpuIn ->
"JTAG_IN_" ::: Signal System JtagIn ->
"" :::
( "CPU_OUTPUT" ::: Signal System CpuOut
, "JTAG_OUT_" ::: Signal System JtagOut)
circuit clk rst input jtagIn =
vexRiscv clk rst input jtagIn

makeTopEntity 'circuit

Expand Down
60 changes: 44 additions & 16 deletions clash-vexriscv-sim/app/VexRiscvSimulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,23 +5,26 @@
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE GADTs #-}

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

import Clash.Prelude

import Protocols.Wishbone
import VexRiscv (Output(iBusWbM2S, dBusWbM2S))
import VexRiscv (CpuOut(iBusWbM2S, dBusWbM2S))

import qualified Data.List as L

import Control.Monad (forM_, when)
import Data.Char (chr)
import Data.Maybe (catMaybes)
import Data.Maybe (catMaybes, fromMaybe)
import System.Environment (getArgs)
import System.IO (putChar, hFlush, stdout)
import Text.Printf (printf)


import Utils.ProgramLoad (loadProgram)
import Utils.Cpu (cpu)
import System.Exit (exitFailure)

--------------------------------------
--
Expand Down Expand Up @@ -59,9 +62,9 @@ debugConfig =
--
{-
InspectBusses
50
0
(Just 300)
0
(Just 100)
True
True
-- -}
Expand All @@ -77,37 +80,56 @@ main = do
withClockResetEnable @System clockGen resetGen enableGen $
loadProgram @System elfFile

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

case debugConfig of
RunCharacterDevice ->
forM_ (sample_lazy @System (bundle (dBus, iBus, writes))) $ \(dS2M, iS2M, write) -> do
when (err dS2M) $
putStrLn "D-bus ERR reply"
forM_ (sample_lazy @System (bundle (register @System (unpack 0) cpuOut, cpuOut))) $
\((_out, write, dS2M0, iS2M0), (out1, _write, _dS2M, _iS2M)) -> do
let
iS2M = fromMaybe emptyWishboneS2M iS2M0
dS2M = fromMaybe emptyWishboneS2M dS2M0

when (err dS2M) $ do
let dBusM2S = dBusWbM2S out1
let dAddr = toInteger (addr dBusM2S) -- `shiftL` 2
printf "D-bus ERR reply % 8X (% 8X)\n" (toInteger $ dAddr `shiftL` 2) (toInteger dAddr)
exitFailure

when (err iS2M) $ do
let iBusM2S = iBusWbM2S out1
let iAddr = toInteger (addr iBusM2S) -- `shiftL` 2
printf "I-bus ERR reply % 8X (% 8X)\n" (toInteger $ iAddr `shiftL` 2) (toInteger iAddr)
printf "%s\n" (showX iBusM2S)
exitFailure

when (err iS2M) $
putStrLn "I-bus ERR reply"

case write of
Just (address, value) | address == 0x0000_1000 -> do
let (_ :: BitVector 24, b :: BitVector 8) = unpack value
putChar $ chr (fromEnum b)
hFlush stdout
pure ()
_ -> pure ()
-- performPrintsToStdout 0x0000_1000 (sample_lazy $ bitCoerce <$> writes)
InspectBusses initCycles uninteresting interesting iEnabled dEnabled -> do

let skipTotal = initCycles + uninteresting

let sampled = case interesting of
Nothing -> L.zip [0 ..] $ sample_lazy @System cpuOut
Just nInteresting ->
let total = initCycles + uninteresting + nInteresting in L.zip [0 ..] $ L.take total $ sample_lazy @System cpuOut
let total = initCycles + uninteresting + nInteresting in
L.zip [0 ..] $ L.take total $ sample_lazy @System cpuOut

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

-- I-bus interactions

Expand Down Expand Up @@ -143,6 +165,9 @@ main = do
<> ")"
putStrLn $ " - iS2M: " <> iResp <> " - " <> iRespData

when (err iBusS2M)
exitFailure

-- D-bus interactions

when (doPrint && dEnabled) $ do
Expand Down Expand Up @@ -192,6 +217,9 @@ main = do
<> writeDat
<> "> - "
putStrLn $ "dS2M: " <> dResp <> dRespData

when (err dBusS2M)
exitFailure
InspectWrites ->
forM_ (catMaybes $ sample_lazy @System writes) $ \(address, value) -> do
printf "W: % 8X <- % 8X\n" (toInteger address) (toInteger value)
39 changes: 31 additions & 8 deletions clash-vexriscv-sim/src/Utils/Cpu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,19 +5,25 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE RecordWildCards #-}

{-# OPTIONS_GHC -Wno-orphans #-}

module Utils.Cpu where

import Clash.Prelude

import Protocols.Wishbone
import VexRiscv
import VexRiscv.JtagTcpBridge as JTag
import VexRiscv.VecToTuple (vecToTuple)

import GHC.Stack (HasCallStack)

import Utils.ProgramLoad (Memory)
import Utils.Interconnect (interconnectTwo)

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

{-
Address space
Expand All @@ -27,37 +33,54 @@ Address space
-}
cpu ::
(HasCallStack, HiddenClockResetEnable dom) =>
Maybe Integer ->
Memory dom ->
Memory dom ->
( Signal dom Output,
( Signal dom CpuOut,
-- writes
Signal dom (Maybe (BitVector 32, BitVector 32)),
-- iBus responses
Signal dom (WishboneS2M (BitVector 32)),
Signal dom (Maybe (WishboneS2M (BitVector 32))),
-- dBus responses
Signal dom (WishboneS2M (BitVector 32))
Signal dom (Maybe (WishboneS2M (BitVector 32)))
)
cpu jtagPort bootIMem bootDMem =
( output
, writes
, mux validI (Just <$> iS2M) (pure Nothing)
, mux validD (Just <$> dS2M) (pure Nothing)
)
cpu bootIMem bootDMem = (output, writes, iS2M, dS2M)
where
output = vexRiscv input
(output, jtagOut) = vexRiscv hasClock hasReset input jtagIn

jtagIn = case jtagPort of
Just port -> vexrJtagBridge (fromInteger port) jtagOut
Nothing -> pure JTag.defaultIn
-- (unbundle -> (jtagIn', _debugReset)) = unsafePerformIO $ jtagTcpBridge' 7894 hasReset (jtagOut <$> output)

dM2S = dBusWbM2S <$> output
validD = fmap busCycle dM2S .&&. fmap strobe dM2S

iM2S = unBusAddr . iBusWbM2S <$> output
validI = fmap busCycle iM2S .&&. fmap strobe iM2S

iS2M = bootIMem (mapAddr (\x -> x - 0x2000_0000) <$> iM2S)
iS2M = bootIMem (mapAddr (\x -> -- trace (printf "I-addr = % 8X (% 8X)\n" (toInteger $ x - 0x2000_0000) (toInteger x))
x - 0x2000_0000) <$> iM2S)

dummy = dummyWb

dummyS2M = dummy dummyM2S
bootDS2M = bootDMem bootDM2S

(dS2M, vecToTuple . unbundle -> (dummyM2S, bootDM2S)) = interconnectTwo
(unBusAddr <$> dM2S)
((\x ->
-- trace (printf "DBUS %08X" (toInteger (addr x)))
x) <$> (unBusAddr <$> dM2S))
((0x0000_0000, dummyS2M) :> (0x4000_0000, bootDS2M) :> Nil)

input =
( \iBus dBus ->
Input
CpuIn
{ timerInterrupt = low,
externalInterrupt = low,
softwareInterrupt = low,
Expand Down
9 changes: 6 additions & 3 deletions clash-vexriscv-sim/src/Utils/Interconnect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,12 @@ interconnectTwo m2s ((aAddr', aS2M') :> (bAddr', bS2M') :> Nil) =
Vec 2 (WishboneM2S 32 4 (BitVector 32))
)
go m@WishboneM2S{..} aAddr aS2M bAddr bS2M
| not (busCycle && strobe) = (emptyWishboneS2M, m :> m :> Nil)
| addr >= bAddr = (bS2M, emptyWishboneM2S :> m { addr = addr - bAddr } :> Nil)
| addr >= aAddr = (aS2M, m { addr = addr - aAddr } :> emptyWishboneM2S :> Nil)
| not (busCycle && strobe) =
(emptyWishboneS2M, m :> m :> Nil)
| addr >= bAddr =
(bS2M, emptyWishboneM2S :> m { addr = addr - bAddr } :> Nil)
| addr >= aAddr =
(aS2M, m { addr = addr - aAddr } :> emptyWishboneM2S :> Nil)
| otherwise =
( emptyWishboneS2M { err = True },
emptyWishboneM2S :> emptyWishboneM2S :> Nil
Expand Down
2 changes: 1 addition & 1 deletion clash-vexriscv-sim/tests/tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ runProgramExpect act n expected = withSystemTempFile "ELF" $ \fp _ -> do

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

let output = L.take (BS.length expected) $
flip mapMaybe (sampleN_lazy n writes) $ \case
Expand Down
23 changes: 18 additions & 5 deletions clash-vexriscv/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,12 @@ OUT_DIR = build_out_dir
VERILATOR_DIR = $(OUT_DIR)/verilator_output
FFI_DIR = src/ffi


VERILATOR_FLAGS = -CFLAGS '-O3 -fPIC' -Wno-fatal +1364-2001ext+v
VERILATOR_FLAGS = -CFLAGS '-O3 -fPIC' -Wno-fatal +1364-2001ext+v --trace

VERILATOR_CFLAGS = $(shell pkg-config --cflags verilator)
FFI_CPPFLAGS = $(VERILATOR_CFLAGS) -fPIC -O3 -I$(VERILATOR_DIR)

all: $(OUT_DIR)/libVexRiscvFFI.a
all: $(OUT_DIR)/libVexRiscvFFI.a # $(OUT_DIR)/libVexRiscvFFI.so

clean:
rm $(VERILATOR_DIR) -rf
Expand All @@ -23,6 +22,8 @@ clean:
$(CPU_DIR)/VexRiscv.v: $(CPU_DIR)/src/main/scala/example/ExampleCpu.scala
cd $(CPU_DIR); sbt "runMain example.ExampleCpu"
cd $(CPU_DIR); sed -i -E '/\/\/ Git hash :.*$$/d' VexRiscv.v
# cd $(CPU_DIR); sed -i 's/module VexRiscv/module VexRiscvInner/g' VexRiscv.v
# cd $(CPU_DIR); cat ../example-cpu/VexRiscvWrapped.v >> VexRiscv.v

$(OUT_DIR)/VexRiscv.v: $(CPU_DIR)/VexRiscv.v
mkdir -p $(OUT_DIR)
Expand All @@ -37,6 +38,10 @@ $(VERILATOR_DIR)/VVexRiscv__ALL.a: $(VERILATOR_DIR)/VVexRiscv.mk
$(OUT_DIR)/impl.o: $(FFI_DIR)/impl.cpp $(FFI_DIR)/interface.h
$(CXX) $(FFI_CPPFLAGS) -c $(FFI_DIR)/impl.cpp -o $(OUT_DIR)/impl.o

$(OUT_DIR)/verilated_vcd_c.o: $(shell pkg-config --variable=includedir verilator)/verilated_vcd_c.cpp
$(CXX) $(FFI_CPPFLAGS) -c $(shell pkg-config --variable=includedir verilator)/verilated_vcd_c.cpp -o $(OUT_DIR)/verilated_vcd_c.o


$(OUT_DIR)/verilated.o: $(shell pkg-config --variable=includedir verilator)/verilated.cpp
$(CXX) $(FFI_CPPFLAGS) -c $(shell pkg-config --variable=includedir verilator)/verilated.cpp -o $(OUT_DIR)/verilated.o

Expand All @@ -46,11 +51,19 @@ $(OUT_DIR)/verilated_threads.o: $(shell pkg-config --variable=includedir verilat
$(OUT_DIR)/VVexRiscv__ALL.a: $(VERILATOR_DIR)/VVexRiscv__ALL.a
cp $(VERILATOR_DIR)/VVexRiscv__ALL.a $(OUT_DIR)/VVexRiscv__ALL.a

$(OUT_DIR)/libVexRiscvFFI.a: $(OUT_DIR)/VVexRiscv__ALL.a $(OUT_DIR)/impl.o $(OUT_DIR)/verilated.o $(OUT_DIR)/verilated_threads.o
$(OUT_DIR)/libVexRiscvFFI.a: $(OUT_DIR)/VVexRiscv__ALL.a $(OUT_DIR)/impl.o $(OUT_DIR)/verilated.o $(OUT_DIR)/verilated_threads.o $(OUT_DIR)/verilated_vcd_c.o
rm -f $(OUT_DIR)/libVexRiscvFFI.a
cp $(OUT_DIR)/VVexRiscv__ALL.a $(OUT_DIR)/libVexRiscvFFI.a
ar r \
$(OUT_DIR)/libVexRiscvFFI.a \
$(OUT_DIR)/impl.o \
$(OUT_DIR)/verilated.o \
$(OUT_DIR)/verilated_threads.o
$(OUT_DIR)/verilated_threads.o \
$(OUT_DIR)/verilated_vcd_c.o

$(OUT_DIR)/libVexRiscvFFI.so: $(OUT_DIR)/libVexRiscvFFI.a
rm -f $(OUT_DIR)/libVexRiscvFFI.so
$(CXX) -shared -o $(OUT_DIR)/libVexRiscvFFI.so \
-Wl,--whole-archive \
$(OUT_DIR)/libVexRiscvFFI.a \
-Wl,--no-whole-archive
2 changes: 2 additions & 0 deletions clash-vexriscv/clash-vexriscv.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,7 @@ library
VexRiscv
VexRiscv.ClockTicks
VexRiscv.FFI
VexRiscv.JtagTcpBridge
VexRiscv.TH
VexRiscv.VecToTuple

Expand All @@ -116,6 +117,7 @@ library
directory >= 1.3 && < 1.4,
filepath,
Glob,
network,
process >= 1.6 && < 1.8,
string-interpolate,
tagged,
Expand Down
4 changes: 4 additions & 0 deletions clash-vexriscv/example-cpu/ExampleCpu.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
# SPDX-FileCopyrightText: 2024 Google LLC
#
# SPDX-License-Identifier: CC0-1.0
debug: !!vexriscv.DebugReport {hardwareBreakpointCount: 5}
Loading

0 comments on commit d4ded17

Please sign in to comment.