Skip to content

Commit

Permalink
WIP: Add JTAG to fmcClockRiscv
Browse files Browse the repository at this point in the history
  • Loading branch information
hiddemoll committed Apr 23, 2024
1 parent 6ab326b commit 211183d
Show file tree
Hide file tree
Showing 4 changed files with 62 additions and 71 deletions.
20 changes: 15 additions & 5 deletions bittide-instances/data/constraints/fmcClockTests.xdc
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,18 @@ set_property IOSTANDARD LVCMOS18 [get_ports "done"]
set_property PACKAGE_PIN H23 [get_ports "success"]
set_property IOSTANDARD LVCMOS18 [get_ports "success"]

set_property PACKAGE_PIN K26 [get_ports "USB_UART_RX"]
set_property IOSTANDARD LVCMOS18 [get_ports "USB_UART_RX"]

set_property PACKAGE_PIN G25 [get_ports "USB_UART_TX"]
set_property IOSTANDARD LVCMOS18 [get_ports "USB_UART_TX"]
# PMOD1_[0..7]
# Note that there are no clock capable pins in this list
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AL14} [get_ports {USB_UART_RXD}]
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AM14} [get_ports {USB_UART_TXD}]
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AP16} [get_ports {JTAG_TCK}]
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AP15} [get_ports {JTAG_TDI}]
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AM16} [get_ports {JTAG_RST}]
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AM15} [get_ports {JTAG_TMS}]
set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AN18} [get_ports {JTAG_TDO}]
# set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AN17} [get_ports {}]

# PMOD1 does not have a clock capable pin. To Vivado's credit, it refuses to
# produce a bitstream if we try to use a non-clock capable pin as a clock. With
# the following line, we tell Vivado to ignore this warning.
set_property CLOCK_DEDICATED_ROUTE FALSE [get_nets JTAG_TCK]
108 changes: 44 additions & 64 deletions bittide-instances/src/Bittide/Instances/Hitl/FmcClock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,83 +14,86 @@ import Clash.Prelude
import Clash.Explicit.Prelude (orReset, noReset)

import Data.Maybe (fromMaybe, isJust)

import Protocols
import Protocols.Internal
import System.Directory
import System.FilePath
import Protocols.Wishbone (WishboneS2M)

import VexRiscv

import Clash.Annotations.TH (makeTopEntity)
import Clash.Cores.UART (ValidBaud)
import Clash.Cores.Xilinx.Ila (IlaConfig(..), Depth(..), ila, ilaConfig)
import Clash.Xilinx.ClockGen (clockWizardDifferential)
import Language.Haskell.TH

import Bittide.ClockControl
import Bittide.ClockControl.Registers (dataCountsWb)
import Bittide.Counter (domainDiffCounter)
import Bittide.DoubleBufferedRam
import Bittide.Hitl (HitlTests, testsFromEnum, hitlVio, singleFpga)
import Bittide.Instances.Domains
import Bittide.ClockControl.Registers (dataCountsWb)
import Bittide.ProcessingElement
import Bittide.ProcessingElement.Util
import Bittide.SharedTypes
import Bittide.Wishbone

import Bittide.Instances.Hitl.FincFdec (TestState(..), Test(..), testStateToDoneSuccess)

import Clash.Cores.Xilinx.GTH (ibufds_gte3, gthCore)
import Clash.Explicit.Reset.Extra (Asserted(..), xpmResetSynchronizer)
import Clash.Hitl (HitlTests, testsFromEnum, hitlVio, singleFpga)

import qualified Clash.Explicit.Prelude as E
import Protocols.Wishbone (WishboneS2M)


onChange :: (HiddenClockResetEnable dom, Eq a, NFDataX a) => Signal dom a -> Signal dom Bool
onChange x = (Just <$> x) ./=. E.register hasClock hasReset hasEnable Nothing (Just <$> x)

-- TODO: This should be removed
instance Default (WishboneS2M (BitVector 32))
where
def = unpack 0

fmcClockRiscv ::
forall dom n .
forall dom .
( HiddenClockResetEnable dom
, 1 <= DomainPeriod dom
, ValidBaud dom 921600
, KnownNat n
, n <= 32 ) =>
, ValidBaud dom 921600 ) =>
"jtagIn" ::: Signal dom JtagIn ->
"sclBs" ::: BiSignalIn 'PullUp dom 1 ->
"sdaIn" ::: Signal dom Bit ->
"datacounts" ::: Vec 1 (Signal dom (DataCount n)) ->
"datacounts" ::: Vec 1 (Signal dom (DataCount 32)) ->
"USB_UART_TX" ::: Signal dom Bit ->
"testSelect" ::: Signal dom (Maybe Test) ->
( "sclBs" ::: BiSignalOut 'PullUp dom 1
( "jtagOut" ::: Signal dom JtagOut
, "sclBs" ::: BiSignalOut 'PullUp dom 1
, "sdaOut" ::: Signal dom Bit
, "muxSelect" ::: BitVector 3
, "clockInitDone" ::: Signal dom Bool
, "testResult" ::: Signal dom TestState
, "USB_UART_RX" ::: Signal dom Bit
)
fmcClockRiscv sclBs sdaIn dataCounts uartIn testSelect =
( writeToBiSignal sclBs sclOut
fmcClockRiscv jtagIn sclBs sdaIn dataCounts uartRx testSelect =
( jtagOut
, writeToBiSignal sclBs sclOut
, fromMaybe 1 <$> sdaOut
, 0b100
, clockInitDoneO
, testResultO
, uartOut
, uartTx
)
where
(_, (CSignal (unbundle -> (sclOut, sdaOut)), CSignal (unbundle -> (clockInitDoneO, testResultO)), CSignal uartOut)) = toSignals
( circuit $ \(i2cIn, statusRegIn, uartRx) -> do
[timeBus, i2cBus, controlRegBus, statusRegBus, dataCountsBus, uartBus, _dummyBus] <- processingElement @dom peConfig -< ()
(uartTx, _uartStatus) <- uartWb d16 d16 (SNat @921600) -< (uartBus, uartRx)
i2cOut <- i2cWb -< (i2cBus, i2cIn)
timeWb -< timeBus
statusRegWb Nothing -< (statusRegIn, statusRegBus)
controlReg <- controlRegWb (False, Busy) -< controlRegBus
dataCountsWb dataCounts -< dataCountsBus
idC -< (i2cOut, controlReg, uartTx)
) ((CSignal i2cIn, CSignal (Just <$> testSelect), CSignal uartIn), (unitCS, unitCS, unitCS))
((_, jtagOut), (i2cOut, controlReg, uartTx)) =
circuitFn (((i2cIn, Just <$> testSelect, uartRx), jtagIn), (pure (), pure (), pure ()))

Circuit circuitFn = circuit $ \((i2cIn, statusRegIn, uartRx), jtag) -> do
[timeBus, i2cBus, controlRegBus, statusRegBus, dataCountsBus, uartBus, _dummyBus] <- processingElement @dom peConfig -< jtag
(uartTx, _uartStatus) <- uartWb d16 d16 (SNat @921600) -< (uartBus, uartRx)
i2cOut <- i2cWb -< (i2cBus, i2cIn)
timeWb -< timeBus
statusRegWb Nothing -< (statusRegIn, statusRegBus)
controlReg <- controlRegWb (False, Busy) -< controlRegBus
dataCountsWb dataCounts -< dataCountsBus
idC -< (i2cOut, controlReg, uartTx)

(sclOut, sdaOut) = unbundle i2cOut
(clockInitDoneO, testResultO) = unbundle controlReg

sclIn = readFromBiSignal sclBs
i2cIn :: Signal dom (Bit, Bit)
Expand All @@ -114,58 +117,35 @@ fmcClockRiscv sclBs sdaIn dataCounts uartIn testSelect =
peConfig =
PeConfig
(0b1000 :> 0b0100 :> 0b0001 :> 0b0010 :> 0b0011 :> 0b0101 :> 0b0110 :> 0b0111 :> (0b0000 :: Unsigned 4) :> Nil)
(Reloadable $ Blob iMem)
(Reloadable $ Blob dMem)

( (_iStart, _iSize, iMem)
, (_dStart, _dSize, dMem)) = $(do

let
findProjectRoot :: IO FilePath
findProjectRoot = goUp =<< getCurrentDirectory
where
goUp :: FilePath -> IO FilePath
goUp path
| isDrive path = error "Could not find 'cabal.project'"
| otherwise = do
exists <- doesFileExist (path </> projectFilename)
if exists then
return path
else
goUp (takeDirectory path)

projectFilename = "cabal.project"

root <- runIO findProjectRoot

let elfPath = root </> "_build/cargo/firmware-binaries/riscv32imc-unknown-none-elf/release/fmc-clock"

memBlobsFromElf BigEndian elfPath Nothing)
(Undefined @(Div (128 * 1024) 4)) -- iMem 128 KiB
(Undefined @(Div (64 * 1024) 4)) -- dMem 64 KiB

fmcClockTests ::
"SYSCLK_125" ::: DiffClock Ext125 ->
"FMC_HPC_GBTCLK1_M2C" ::: DiffClock Ext200 ->
"JTAG" ::: Signal Basic125 JtagIn ->
"sclBs" ::: BiSignalIn 'PullUp Basic125 1 ->
"sdaIn" ::: Signal Basic125 Bit ->
"USB_UART_TX" ::: Signal Basic125 Bit ->
"USB_UART_TXD" ::: Signal Basic125 Bit ->
( "sclBs" ::: BiSignalOut 'PullUp Basic125 1
, "sdaOut" ::: Signal Basic125 Bit
, "muxSelect" ::: BitVector 3
, "" :::
( "done" ::: Signal Basic125 Bool
, "success" ::: Signal Basic125 Bool
)
, "USB_UART_RX" ::: Signal Basic125 Bit
, "USB_UART_RXD" ::: Signal Basic125 Bit
, "JTAG" ::: Signal Basic125 JtagOut
)
fmcClockTests sysClkDiff fmcClkDiff sclBsIn sdaIn uartIn =
fmcClockTests sysClkDiff fmcClkDiff jtagIn sclBsIn sdaIn uartIn =
fmcClockIla `hwSeqX`
(sclBsOut, sdaOut, muxSelect, (testDone, testSuccess), uartOut)
(sclBsOut, sdaOut, muxSelect, (testDone, testSuccess), uartOut, jtagOut)
where
(sysClk, sysRst :: Reset Basic125) = clockWizardDifferential sysClkDiff noReset

(sclBsOut, sdaOut, muxSelect, clockInitDone, testResult, uartOut) =
(jtagOut, sclBsOut, sdaOut, muxSelect, clockInitDone, testResult, uartOut) =
withClockResetEnable sysClk sysRst enableGen $
fmcClockRiscv sclBsIn sdaIn (domainDiff :> Nil) uartIn testInput
fmcClockRiscv jtagIn sclBsIn sdaIn (domainDiff :> Nil) uartIn testInput

fmcClk = ibufds_gte3 fmcClkDiff :: Clock Ext200

Expand Down Expand Up @@ -219,8 +199,8 @@ fmcClockTests sysClkDiff fmcClkDiff sclBsIn sdaIn uartIn =
fmcClockIla :: Signal Basic125 ()
fmcClockIla = setName @"fmcClockIla" $ ila
(ilaConfig $
"trigger"
:> "capture"
"trigger_0"
:> "capture_0"
:> "probe_testInput"
:> "probe_testDone"
:> "probe_testSuccess"
Expand Down
3 changes: 2 additions & 1 deletion bittide-shake/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -201,7 +201,8 @@ targets = map enforceValidTarget
{targetPostProcess = Just "post-board-test-extended"}
, testTarget "Bittide.Instances.Hitl.BoardTest.boardTestSimple"
, testTarget "Bittide.Instances.Hitl.FincFdec.fincFdecTests"
, testTarget "Bittide.Instances.Hitl.FmcClock.fmcClockTests"
, (testTarget "Bittide.Instances.Hitl.FmcClock.fmcClockTests")
{targetExtraXdc = ["jtag.xdc"]}
, testTarget "Bittide.Instances.Hitl.FullMeshHwCc.fullMeshHwCcTest"
, testTarget "Bittide.Instances.Hitl.FullMeshHwCc.fullMeshHwCcWithRiscvTest"
, testTarget "Bittide.Instances.Hitl.FullMeshSwCc.fullMeshSwCcTest"
Expand Down
2 changes: 1 addition & 1 deletion firmware-binaries/fmc-clock/memory.x
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ SPDX-License-Identifier: CC0-1.0

MEMORY
{
IMEM : ORIGIN = 0x80000000, LENGTH = 64K
IMEM : ORIGIN = 0x80000000, LENGTH = 128K
DMEM : ORIGIN = 0x40000000, LENGTH = 64K
}

Expand Down

0 comments on commit 211183d

Please sign in to comment.