diff --git a/.github/synthesis/staging.json b/.github/synthesis/staging.json index cbb1305c2..9a578536b 100644 --- a/.github/synthesis/staging.json +++ b/.github/synthesis/staging.json @@ -1,5 +1,6 @@ [ {"top": "clockControlDemo0", "stage": "bitstream"}, - {"top": "simpleHardwareInTheLoopTest", "stage": "test"}, - {"top": "extendedHardwareInTheLoopTest", "stage": "test"} + {"top": "extendedHardwareInTheLoopTest", "stage": "test"}, + {"top": "fdecTest", "stage": "test"}, + {"top": "simpleHardwareInTheLoopTest", "stage": "test"} ] diff --git a/bittide-instances/bin/Shake.hs b/bittide-instances/bin/Shake.hs index 2304b66e5..621c912d1 100644 --- a/bittide-instances/bin/Shake.hs +++ b/bittide-instances/bin/Shake.hs @@ -38,6 +38,9 @@ import qualified Bittide.Instances.ScatterGather as ScatterGather import qualified Bittide.Instances.Si539xSpi as Si539xSpi import qualified Bittide.Instances.StabilityChecker as StabilityChecker import qualified Bittide.Instances.Synchronizer as Synchronizer + +import qualified Bittide.Instances.Tests.FincFdec as FincFdec + import qualified Clash.Util.Interpolate as I import qualified Language.Haskell.TH as TH import qualified System.Directory as Directory @@ -199,6 +202,14 @@ defTarget name = Target , targetHasTest = False } +testTarget :: TH.Name -> Target +testTarget name = Target + { targetName = name + , targetHasXdc = True + , targetHasVio = True + , targetHasTest = True + } + enforceValidTarget :: Target -> Target enforceValidTarget target@Target{..} | targetHasTest && not targetHasVio = @@ -210,17 +221,7 @@ enforceValidTarget target@Target{..} -- | All synthesizable targets targets :: [Target] targets = map enforceValidTarget - [ (defTarget 'BoardTest.simpleHardwareInTheLoopTest) - { targetHasXdc = True - , targetHasVio = True - , targetHasTest = True - } - , (defTarget 'BoardTest.extendedHardwareInTheLoopTest) - { targetHasXdc = True - , targetHasVio = True - , targetHasTest = True - } - , defTarget 'Calendar.switchCalendar1k + [ defTarget 'Calendar.switchCalendar1k , defTarget 'Calendar.switchCalendar1kReducedPins , defTarget 'ClockControl.callisto3 , defTarget 'Counter.counterReducedPins @@ -235,6 +236,10 @@ targets = map enforceValidTarget , defTarget 'Si539xSpi.si5391Spi , defTarget 'StabilityChecker.stabilityChecker_3_1M , defTarget 'Synchronizer.safeDffSynchronizer + + , testTarget 'BoardTest.extendedHardwareInTheLoopTest + , testTarget 'BoardTest.simpleHardwareInTheLoopTest + , testTarget 'FincFdec.fdecTest ] shakeOpts :: ShakeOptions diff --git a/bittide-instances/bittide-instances.cabal b/bittide-instances/bittide-instances.cabal index 30df26c99..1378c4535 100644 --- a/bittide-instances/bittide-instances.cabal +++ b/bittide-instances/bittide-instances.cabal @@ -111,6 +111,8 @@ library Bittide.Instances.StabilityChecker Bittide.Instances.Synchronizer + Bittide.Instances.Tests.FincFdec + Clash.Shake.Extra Clash.Shake.Flags Clash.Shake.Vivado diff --git a/bittide-instances/data/constraints/fdecTest.xdc b/bittide-instances/data/constraints/fdecTest.xdc new file mode 100644 index 000000000..04f13dfaf --- /dev/null +++ b/bittide-instances/data/constraints/fdecTest.xdc @@ -0,0 +1,44 @@ +# SPDX-FileCopyrightText: 2022-2023 Google LLC +# +# SPDX-License-Identifier: Apache-2.0 +# +# NOTE: This configuration is only valid for the leftmost FPGA in the demo rack. +# +# Color | FPGA pin | LVLShift | Connection +# --------|---------------|---------------|--------- +# Grey | PMOD0_0 | IO1 | SWDIO +# Blue | PMOD0_1 | IO2 | FINC +# Yellow | PMOD0_2 | IO3 | MOSI/SDIO +# Red | PMOD0_3 | IO4 | SCLK +# White | PMOD0_4 | IO5 | SWCLK +# Purple | PMOD0_5 | IO6 | FDEC +# Green | PMOD0_6 | IO7 | CSB +# Orange | PMOD0_7 | IO8 | MISO/SDO +# Black | Not connected | Not connected | GND (SWD) +# Brown | PMOD_GND | GND | GND (SPI) +# +# The data wire of the external reset button is connected to PMOD1_3. + + +# CLK_125MHZ +set_property BOARD_PART_PIN sysclk_125_p [get_ports {CLK_125MHZ_P}] +set_property BOARD_PART_PIN sysclk_125_n [get_ports {CLK_125MHZ_N}] + +# USER_SMA_CLOCK +set_property -dict {IOSTANDARD LVDS PACKAGE_PIN D23} [get_ports {USER_SMA_CLOCK_P}] +set_property -dict {IOSTANDARD LVDS PACKAGE_PIN C23} [get_ports {USER_SMA_CLOCK_N}] + +# GPIO_LED_0_LS +set_property BOARD_PART_PIN GPIO_LED_0_LS [get_ports {done}] +# GPIO_LED_1_LS +set_property BOARD_PART_PIN GPIO_LED_1_LS [get_ports {success}] + +# PMOD0_[0..7] +# set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AK25} [get_ports {SWDIO}] +set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AN21} [get_ports {FINC}] +set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AH18} [get_ports {MOSI}] +set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AM19} [get_ports {SCLK}] +# set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AE26} [get_ports {SWCLK}] +set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AF25} [get_ports {FDEC}] +set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AE21} [get_ports {CSB}] +set_property -dict {IOSTANDARD LVCMOS12 PACKAGE_PIN AM17} [get_ports {MISO}] diff --git a/bittide-instances/data/tcl/HardwareTest.tcl b/bittide-instances/data/tcl/HardwareTest.tcl index 268127979..e10cd6fa6 100644 --- a/bittide-instances/data/tcl/HardwareTest.tcl +++ b/bittide-instances/data/tcl/HardwareTest.tcl @@ -150,6 +150,7 @@ proc run_single_test {start_probe} { # Verify that `done` is not set before starting the test set_property OUTPUT_VALUE 0 $start_probe commit_hw_vio [get_hw_vios hw_vio_1] + after 10 refresh_hw_vio [get_hw_vios hw_vio_1] set done [get_property INPUT_VALUE [get_hw_probes probe_test_done]] if {$done != 0} { diff --git a/bittide-instances/src/Bittide/Instances/MVPs.hs b/bittide-instances/src/Bittide/Instances/MVPs.hs index b65d9f0e2..74fab24a2 100644 --- a/bittide-instances/src/Bittide/Instances/MVPs.hs +++ b/bittide-instances/src/Bittide/Instances/MVPs.hs @@ -4,6 +4,9 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE NumericUnderscores #-} + +{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-} + module Bittide.Instances.MVPs where import Clash.Prelude diff --git a/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs b/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs new file mode 100644 index 000000000..61422a9c8 --- /dev/null +++ b/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs @@ -0,0 +1,219 @@ +-- SPDX-FileCopyrightText: 2022-2023 Google LLC +-- +-- SPDX-License-Identifier: Apache-2.0 + +{-# LANGUAGE NumericUnderscores #-} + +-- | A couple of tests testing clock board programming, and subsequently the +-- FINC and FDEC pins. +module Bittide.Instances.Tests.FincFdec where + +import Clash.Annotations.TH (makeTopEntity) +import Clash.Explicit.Prelude +import Clash.Prelude (withClockResetEnable) + +import Bittide.Arithmetic.Time +import Bittide.Counter (domainDiffCounter) +import Bittide.ClockControl (SpeedChange(NoChange, SlowDown, SpeedUp), speedChangeToFincFdec) +import Bittide.ClockControl.Si539xSpi (si539xSpi, ConfigState(Finished)) +import Bittide.Instances.Domains + +import Clash.Xilinx.ClockGen (clockWizardDifferential) + +import Clash.Cores.Xilinx.Extra (ibufds) +import Clash.Cores.Xilinx.VIO (vioProbe) +import Clash.Cores.Xilinx.Xpm.Cdc.Single (xpmCdcSingle) + +import qualified Bittide.ClockControl.Si5395J as Si5395J + +data TestState = Busy | Fail | Success +data Test = Fdec | Finc + +testStateToDoneSuccess :: TestState -> (Bool, Bool) +testStateToDoneSuccess = \case + Busy -> (False, False) + Fail -> (True, False) + Success -> (True, True) + +noReset :: KnownDomain dom => Reset dom +noReset = unsafeFromHighPolarity (pure False) + +eitherReset :: KnownDomain dom => Reset dom -> Reset dom -> Reset dom +eitherReset (unsafeToHighPolarity -> rstA) (unsafeToHighPolarity -> rstB) = + unsafeFromHighPolarity (rstA .||. rstB) + +bothReset :: KnownDomain dom => Reset dom -> Reset dom -> Reset dom +bothReset (unsafeToHighPolarity -> rstA) (unsafeToHighPolarity -> rstB) = + unsafeFromHighPolarity (rstA .&&. rstB) + +fdecTestGo :: + Clock Basic200A -> + Reset Basic200A -> + Clock Basic200B -> + Signal Basic200A Test -> + "MISO" ::: Signal Basic200A Bit -> -- SPI + "" ::: + ( Signal Basic200A TestState + + -- Freq increase / freq decrease request to clock board + , ( "FINC" ::: Signal Basic200A Bool + , "FDEC" ::: Signal Basic200A Bool + ) + + -- SPI to clock board: + , "" ::: + ( "SCLK" ::: Signal Basic200A Bool + , "MOSI" ::: Signal Basic200A Bit + , "CSB" ::: Signal Basic200A Bool + ) + + -- Debug signals: + , "" ::: + ( "SPI_BUSY" ::: Signal Basic200A Bool + , "SPI_STATE" ::: Signal Basic200A (BitVector 40) + , "SI_LOCKED" ::: Signal Basic200A Bool + , "COUNTER_ACTIVE" ::: Signal Basic200A Bool + , "COUNTER" ::: Signal Basic200A (Signed 32) + ) + ) +fdecTestGo clk rst clkControlled testSelect miso = + (testResult, fIncDec, spiOut, debugSignals) + where + debugSignals = (spiBusy, pack <$> spiState, siClkLocked, counterActive, counter) + + (_, spiBusy, spiState@(fmap (==Finished) -> siClkLocked), spiOut) = + withClockResetEnable clk rst enableGen $ + si539xSpi + Si5395J.testConfig6_200_on_0a_and_0 + -- Si5395J.testConfigAll200 + (SNat @(Nanoseconds 1000)) + (pure Nothing) + miso + + rstTest = unsafeFromLowPolarity siClkLocked + + rstControlled = + unsafeFromLowPolarity $ + xpmCdcSingle clk clkControlled $ -- improvised reset syncer + unsafeToLowPolarity rst + + (counter, counterActive) = + unbundle $ + -- Note that in a "real" Bittide system the clocks would be wired up the + -- other way around: the controlled domain would be the target domain. We + -- don't do that here because we know 'rstControlled' will come out of + -- reset much earlier than 'rstTest'. Doing it the "proper" way would + -- therefore introduce extra complexity, without adding to the test's + -- coverage. + domainDiffCounter clkControlled rstControlled clk rstTest + + fIncDec = unbundle $ speedChangeToFincFdec clk rst fIncDecRequest + + (fIncDecRequest, testResult) = + mealyB clk rstTest enableGen go () (counter, testSelect) + + go :: () -> (Signed 32, Test) -> ((), (SpeedChange, TestState)) + go () (n, Fdec) = ((), goFdec n) + go () (n, Finc) = ((), goFinc n) + + +goFdec :: Signed 32 -> (SpeedChange, TestState) +goFdec n + | n > 20_000 = (NoChange, Fail) + | n < -20_000 = (NoChange, Success) + | otherwise = (SlowDown, Busy) + +goFinc :: Signed 32 -> (SpeedChange, TestState) +goFinc n + | n > 20_000 = (NoChange, Success) + | n < -20_000 = (NoChange, Fail) + | otherwise = (SpeedUp, Busy) + +fdecTest :: + -- Pins from internal oscillator: + "CLK_125MHZ_P" ::: Clock Basic125 -> + "CLK_125MHZ_N" ::: Clock Basic125 -> + + -- Pins from clock board: + "USER_SMA_CLOCK_P" ::: Clock Basic200B -> + "USER_SMA_CLOCK_N" ::: Clock Basic200B -> + "MISO" ::: Signal Basic200A Bit -> -- SPI + + "" ::: + ( "" ::: + ( "done" ::: Signal Basic200A Bool + , "success" ::: Signal Basic200A Bool + ) + + -- Freq increase / freq decrease request to clock board + , "" ::: + ( "FINC" ::: Signal Basic200A Bool + , "FDEC" ::: Signal Basic200A Bool + ) + + -- SPI to clock board: + , "" ::: + ( "SCLK" ::: Signal Basic200A Bool + , "MOSI" ::: Signal Basic200A Bit + , "CSB" ::: Signal Basic200A Bool + ) + ) +fdecTest clkP clkN controlledClockP controlledClockN spiIn = + ((testDone, testSuccess), fIncDec, spiOut) + where + clkControlled = ibufds controlledClockP controlledClockN + + (clk, clkStable0) = clockWizardDifferential (SSymbol @"pll") clkN clkP noReset + clkStable1 = xpmCdcSingle clk clk clkStable0 -- improvised reset syncer + + clkStableRst = unsafeFromLowPolarity clkStable1 + startFdecTestRst = unsafeFromLowPolarity startFdecTest + startFincTestRst = unsafeFromLowPolarity startFincTest + testRst = eitherReset clkStableRst (bothReset startFdecTestRst startFincTestRst) + testRstBool = unsafeToHighPolarity testRst + + (fInc, fDec) = fIncDec + + testF = mux startFdecTest (pure Fdec) (pure Finc) + + (testResult, fIncDec, spiOut, debugSignals) = + fdecTestGo clk testRst clkControlled testF spiIn + + (testDone, testSuccess) = unbundle $ testStateToDoneSuccess <$> testResult + + (spiBusy, spiState, siClkLocked, counterActive, counter) = debugSignals + + (startFdecTest, startFincTest) = unbundle $ + vioProbe + ( "probe_test_done" + :> "probe_test_success" + + -- Debug signals: + :> "probe_clkStable1" + :> "probe_testRstBool" + :> "probe_spiBusy" + :> "probe_spiState" + :> "probe_siClkLocked" + :> "probe_counterActive" + :> "probe_counter" + :> "probe_fInc" + :> "probe_fDec" + :> Nil) + ("probe_test_start_fdec" :> "probe_test_start_finc" :> Nil) + (False, False) + clk + testDone + testSuccess + + -- Debug signals + clkStable1 + testRstBool + spiBusy + spiState + siClkLocked + counterActive + counter + fInc + fDec +{-# NOINLINE fdecTest #-} +makeTopEntity 'fdecTest diff --git a/bittide/src/Bittide/ClockControl.hs b/bittide/src/Bittide/ClockControl.hs index 4b88350a0..703cef9bb 100644 --- a/bittide/src/Bittide/ClockControl.hs +++ b/bittide/src/Bittide/ClockControl.hs @@ -6,6 +6,8 @@ {-# LANGUAGE NamedFieldPuns #-} {-# OPTIONS_GHC -Wno-orphans #-} +{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-} + -- | Clock controller types and some constants/defaults. module Bittide.ClockControl ( ClockControlConfig (..) @@ -16,6 +18,7 @@ module Bittide.ClockControl , pessimisticSettleCycles , targetDataCount , clockPeriodFs + , speedChangeToFincFdec ) where @@ -26,7 +29,7 @@ import Data.Proxy (Proxy(..)) import GHC.Stack (HasCallStack) import Bittide.Arithmetic.Ppm -import Bittide.Arithmetic.Time (microseconds) +import Bittide.Arithmetic.Time (PeriodToCycles, Nanoseconds, Microseconds, microseconds) import Data.Csv @@ -120,6 +123,56 @@ data SpeedChange | NoChange deriving (Eq, Show, Generic, ShowX, NFDataX) +data ToFincFdecState + = Wait (Unsigned 32) + | Pulse (Unsigned 32) SpeedChange + | Idle + deriving (Generic, NFDataX) + +-- | Convert 'SpeedChange' to a pair of (FINC, FDEC). This is currently hardcoded +-- to work on the Si5395 constraints: +-- +-- * Minimum Pulse Width: 100 ns +-- * Update Rate: 1 us +-- +-- TODO: De-hardcode +speedChangeToFincFdec :: + forall dom . + KnownDomain dom => + Clock dom -> + Reset dom -> + Signal dom SpeedChange -> + Signal dom (Bool, Bool) +speedChangeToFincFdec clk rst = + fmap conv . mealy clk rst enableGen go (Wait waitCycles) + where + pulseCycles :: Unsigned 32 + pulseCycles = + case clockPeriod @dom of + SNat -> natToNum @(PeriodToCycles dom (Nanoseconds 100)) + + waitCycles :: Unsigned 32 + waitCycles = + case clockPeriod @dom of + SNat -> natToNum @(PeriodToCycles dom (Microseconds 1)) + + go :: ToFincFdecState -> SpeedChange -> (ToFincFdecState, SpeedChange) + go (Wait n) _s + | n == 0 = (Idle, NoChange) + | otherwise = (Wait (n - 1), NoChange) + + go (Pulse n s) _s + | n == 0 = (Wait waitCycles, s) + | otherwise = (Pulse (n - 1) s, s) + + go Idle NoChange = (Idle, NoChange) + go Idle s = (Pulse pulseCycles s, NoChange) + + -- FINC FDEC + conv NoChange = (False, False) + conv SpeedUp = (True, False) + conv SlowDown = (False, True) + instance ToField SpeedChange where toField SpeedUp = "speedUp" toField SlowDown = "slowDown" @@ -151,6 +204,7 @@ defClockConfig = ClockControlConfig { cccPessimisticPeriod = pessimisticPeriod , cccPessimisticSettleCycles = pessimisticSettleCycles self , cccSettlePeriod = microseconds 1 + -- , cccMinimumPulseWidth = nanoseconds 100 , cccStepSize = stepSize , cccBufferSize = d12 -- 2**12 ~ 4096 , cccDeviation = Ppm 100 diff --git a/bittide/src/Bittide/ClockControl/Si539xSpi.hs b/bittide/src/Bittide/ClockControl/Si539xSpi.hs index e6c519f43..eeb3642cc 100644 --- a/bittide/src/Bittide/ClockControl/Si539xSpi.hs +++ b/bittide/src/Bittide/ClockControl/Si539xSpi.hs @@ -1,9 +1,10 @@ -- SPDX-FileCopyrightText: 2022-2023 Google LLC -- -- SPDX-License-Identifier: Apache-2.0 -{-# OPTIONS_GHC -fconstraint-solver-iterations=9 #-} +{-# OPTIONS_GHC -fconstraint-solver-iterations=20 #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE RecordWildCards #-} @@ -81,28 +82,30 @@ spiCommandToBytes = \case -- | State of the configuration circuit in 'si539xSpi'. data ConfigState dom entries - = WaitForReady Bool + = WaitForReady Bool -- 0 -- ^ Continuously read from 'Address' 0xFE at any 'Page', if this operations returns -- 0x0F twice in a row, the device is considered to be ready for operation. - | ResetDriver Bool + | ResetDriver Bool -- 1 -- ^ Always after a @WaitForReady False@ state, we reset the SPI driver to make sure -- it first sets the page and address again. - | FetchReg (Index entries) + | FetchReg (Index entries) -- 2 -- ^ Fetches the 'RegisterEntry' at the 'Index' to be written to the @Si539x@ chip. - | WriteEntry (Index entries) + | WriteEntry (Index entries) -- 3 -- ^ Writes the 'RegisterEntry' at the 'Index' to the @Si539x@ chip. - | ReadEntry (Index entries) + | ReadEntry (Index entries) -- 4 -- ^ Checks if the 'RegisterEntry' at the 'Index' was correctly written to the @Si539x@ chip. - | Error (Index entries) + | Error (Index entries) -- 5 -- ^ The 'RegisterEntry' at the 'Index' was not correctly written to the @Si539x@ chip. - | WaitForLock + | WaitForLock -- 6 -- ^ Continuously read from 'Address' 0x0C at 'Page' 0x00 until it returns bit 3 is 0. - | Finished + | Finished -- 7 -- ^ All entries in the 'Si539xRegisterMap' were correctly written to the @Si539x@ chip. - | Wait (Index (PeriodToCycles dom (Milliseconds 300))) (Index entries) + | Wait (Index (PeriodToCycles dom (Milliseconds 300))) (Index entries) -- 8 -- ^ Waits for the Si539X to be calibrated after writing the configuration preamble from 'Si539xRegisterMap'. deriving (Show, Generic, NFDataX, Eq) +instance (1 <= entries, KnownNat (DomainPeriod dom), KnownNat entries) => BitPack (ConfigState dom entries) + -- | Utility function to retrieve the entry 'Index' from the 'ConfigState'. getStateAddress :: KnownNat entries => ConfigState dom entries -> Index entries getStateAddress = \case @@ -219,7 +222,7 @@ data DriverState dom = DriverState -- ^ Current communication transaction. , commandAcknowledged :: Acknowledge -- ^ Whether or not the current transaction has already been acknowledged. - , idleCycles :: Index (PeriodToCycles dom (Nanoseconds 95)) + , idleCycles :: Index (PeriodToCycles dom (Nanoseconds 950)) -- ^ After communication, slave select must be high for at least 95ns. } deriving (Generic, NFDataX)