diff --git a/.github/synthesis/all.json b/.github/synthesis/all.json index 50dba47bb..bb6a283b3 100644 --- a/.github/synthesis/all.json +++ b/.github/synthesis/all.json @@ -17,6 +17,6 @@ {"top": "switchCalendar1kReducedPins", "stage": "netlist"}, {"top": "extendedHardwareInTheLoopTest", "stage": "test", "targets": "All" }, - {"top": "fdecTest", "stage": "test", "targets": "Specific [-1]"}, + {"top": "fincFdecTests", "stage": "test", "targets": "Specific [-1]"}, {"top": "simpleHardwareInTheLoopTest", "stage": "test", "targets": "All" } ] diff --git a/.github/synthesis/staging.json b/.github/synthesis/staging.json index 5312e034e..22278834e 100644 --- a/.github/synthesis/staging.json +++ b/.github/synthesis/staging.json @@ -1,6 +1,6 @@ [ {"top": "clockControlDemo0", "stage": "bitstream"}, {"top": "extendedHardwareInTheLoopTest", "stage": "test", "targets": "All"}, - {"top": "fdecTest", "stage": "test", "targets": "Specific [-1]"}, + {"top": "fincFdecTests", "stage": "test", "targets": "Specific [-1]"}, {"top": "simpleHardwareInTheLoopTest", "stage": "test", "targets": "All"} ] diff --git a/bittide-extra/bittide-extra.cabal b/bittide-extra/bittide-extra.cabal index 3e12762ec..53e2a493a 100644 --- a/bittide-extra/bittide-extra.cabal +++ b/bittide-extra/bittide-extra.cabal @@ -75,6 +75,8 @@ library exposed-modules: Bittide.Extra.Maybe Bittide.Extra.Wishbone + Clash.Reset.Extra + Clash.Sized.Vector.Extra test-suite doctests type: exitcode-stdio-1.0 diff --git a/bittide-extra/src/Clash/Reset/Extra.hs b/bittide-extra/src/Clash/Reset/Extra.hs new file mode 100644 index 000000000..63d76a8af --- /dev/null +++ b/bittide-extra/src/Clash/Reset/Extra.hs @@ -0,0 +1,18 @@ +-- SPDX-FileCopyrightText: 2022-2023 Google LLC +-- +-- SPDX-License-Identifier: Apache-2.0 + +module Clash.Reset.Extra where + +import Clash.Explicit.Prelude + +noReset :: KnownDomain dom => Reset dom +noReset = unsafeFromHighPolarity (pure False) + +orReset :: KnownDomain dom => Reset dom -> Reset dom -> Reset dom +orReset (unsafeToHighPolarity -> rstA) (unsafeToHighPolarity -> rstB) = + unsafeFromHighPolarity (rstA .||. rstB) + +andReset :: KnownDomain dom => Reset dom -> Reset dom -> Reset dom +andReset (unsafeToHighPolarity -> rstA) (unsafeToHighPolarity -> rstB) = + unsafeFromHighPolarity (rstA .&&. rstB) diff --git a/bittide-extra/src/Clash/Sized/Vector/Extra.hs b/bittide-extra/src/Clash/Sized/Vector/Extra.hs new file mode 100644 index 000000000..b505b83c5 --- /dev/null +++ b/bittide-extra/src/Clash/Sized/Vector/Extra.hs @@ -0,0 +1,18 @@ +-- SPDX-FileCopyrightText: 2022-2023 Google LLC +-- +-- SPDX-License-Identifier: Apache-2.0 + +module Clash.Sized.Vector.Extra where + +import Clash.Explicit.Prelude +import Data.Maybe (fromMaybe) + +find :: KnownNat n => (a -> Bool) -> Vec n a -> Maybe a +find f = foldl (<|>) Nothing . map go + where + go a + | f a = Just a + | otherwise = Nothing + +findWithDefault :: KnownNat n => a -> (a -> Bool) -> Vec n a -> a +findWithDefault a f = fromMaybe a . find f diff --git a/bittide-instances/bin/Shake.hs b/bittide-instances/bin/Shake.hs index 621c912d1..9d369edc2 100644 --- a/bittide-instances/bin/Shake.hs +++ b/bittide-instances/bin/Shake.hs @@ -239,7 +239,7 @@ targets = map enforceValidTarget , testTarget 'BoardTest.extendedHardwareInTheLoopTest , testTarget 'BoardTest.simpleHardwareInTheLoopTest - , testTarget 'FincFdec.fdecTest + , testTarget 'FincFdec.fincFdecTests ] shakeOpts :: ShakeOptions diff --git a/bittide-instances/data/constraints/fdecTest.xdc b/bittide-instances/data/constraints/fincFdecTests.xdc similarity index 100% rename from bittide-instances/data/constraints/fdecTest.xdc rename to bittide-instances/data/constraints/fincFdecTests.xdc diff --git a/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs b/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs index 6e3bdef19..510d80d7e 100644 --- a/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs +++ b/bittide-instances/src/Bittide/Instances/Tests/FincFdec.hs @@ -12,6 +12,9 @@ import Clash.Annotations.TH (makeTopEntity) import Clash.Explicit.Prelude import Clash.Prelude (withClockResetEnable) +import Clash.Reset.Extra (orReset, noReset) +import Clash.Sized.Vector.Extra (findWithDefault) + import Bittide.Arithmetic.Time import Bittide.Counter (domainDiffCounter) import Bittide.ClockControl (SpeedChange(NoChange, SlowDown, SpeedUp), speedChangeToFincFdec) @@ -27,7 +30,10 @@ import Clash.Cores.Xilinx.Xpm.Cdc.Single (xpmCdcSingle) import qualified Bittide.ClockControl.Si5395J as Si5395J data TestState = Busy | Fail | Success -data Test = Fdec | Finc +data Test = FDec | FInc | FDecInc | FIncDec deriving (Enum, Generic, NFDataX) + +allTests :: Vec 4 Test +allTests = FDec :> FInc :> FDecInc :> FIncDec :> Nil testStateToDoneSuccess :: TestState -> (Bool, Bool) testStateToDoneSuccess = \case @@ -35,18 +41,7 @@ testStateToDoneSuccess = \case 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 :: +goFincFdecTests :: Clock Basic200A -> Reset Basic200A -> Clock Basic200B -> @@ -76,7 +71,7 @@ fdecTestGo :: , "COUNTER" ::: Signal Basic200A (Signed 32) ) ) -fdecTestGo clk rst clkControlled testSelect miso = +goFincFdecTests clk rst clkControlled testSelect miso = (testResult, fIncDec, spiOut, debugSignals) where debugSignals = (spiBusy, pack <$> spiState, siClkLocked, counterActive, counter) @@ -85,8 +80,7 @@ fdecTestGo clk rst clkControlled testSelect miso = withClockResetEnable clk rst enableGen $ si539xSpi Si5395J.testConfig6_200_on_0a_and_0 - -- Si5395J.testConfigAll200 - (SNat @(Nanoseconds 1000)) + (SNat @(Microseconds 1)) (pure Nothing) miso @@ -109,27 +103,57 @@ fdecTestGo clk rst clkControlled testSelect miso = fIncDec = unbundle $ speedChangeToFincFdec clk rstTest 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 :: + (fIncDecRequest, testResult) = unbundle $ + (!!) + <$> bundle (fDecResult :> fIncResult :> fDecIncResult :> fIncDecResult :> Nil) + <*> fmap fromEnum testSelect + + fDecResult = goFdec <$> counter + fIncResult = goFinc <$> counter + fDecIncResult = mealy clk rstTest enableGen goFdecFinc FDec counter + fIncDecResult = mealy clk rstTest enableGen goFincFdec FInc counter + + -- Keep pressing FDEC, expect counter to go below -20_000 + goFdec :: Signed 32 -> (SpeedChange, TestState) + goFdec n + | n > 20_000 = (NoChange, Fail) + | n < -20_000 = (NoChange, Success) + | otherwise = (SlowDown, Busy) + + -- Keep pressing FINC, expect counter to go above 20_000 + goFinc :: Signed 32 -> (SpeedChange, TestState) + goFinc n + | n > 20_000 = (NoChange, Success) + | n < -20_000 = (NoChange, Fail) + | otherwise = (SpeedUp, Busy) + + -- Keep pressing FDEC, expect counter to go below -20_000, then keep pressing + -- FINC, expect counter to go above 0. + goFdecFinc :: Test -> Signed 32 -> (Test, (SpeedChange, TestState)) + goFdecFinc FDec n + | n > 20_000 = (FDec, (NoChange, Fail)) + | n < -20_000 = (FInc, (NoChange, Busy)) + | otherwise = (FDec, (SlowDown, Busy)) + goFdecFinc FInc n + | n > 0 = (FInc, (NoChange, Success)) + | n < -60_000 = (FInc, (NoChange, Fail)) + | otherwise = (FInc, (SpeedUp, Busy)) + goFdecFinc s _ = (s, (NoChange, Fail)) -- Illegal state + + -- Keep pressing FINC, expect counter to go above 20_000, then keep pressing + -- FDEC, expect counter to go below 0. + goFincFdec :: Test -> Signed 32 -> (Test, (SpeedChange, TestState)) + goFincFdec FInc n + | n > 20_000 = (FDec, (NoChange, Busy)) + | n < -20_000 = (FInc, (NoChange, Fail)) + | otherwise = (FInc, (SpeedUp, Busy)) + goFincFdec FDec n + | n > 60_000 = (FDec, (NoChange, Fail)) + | n < 0 = (FDec, (NoChange, Success)) + | otherwise = (FDec, (SlowDown, Busy)) + goFincFdec s _ = (s, (NoChange, Fail)) -- Illegal state + +fincFdecTests :: -- Pins from internal oscillator: "CLK_125MHZ_P" ::: Clock Basic125 -> "CLK_125MHZ_N" ::: Clock Basic125 -> @@ -158,7 +182,7 @@ fdecTest :: , "CSB" ::: Signal Basic200A Bool ) ) -fdecTest clkP clkN controlledClockP controlledClockN spiIn = +fincFdecTests clkP clkN controlledClockP controlledClockN spiIn = ((testDone, testSuccess), fIncDec, spiOut) where clkControlled = ibufds controlledClockP controlledClockN @@ -167,23 +191,23 @@ fdecTest clkP clkN controlledClockP controlledClockN spiIn = clkStable1 = xpmCdcSingle clk clk clkStable0 -- improvised reset syncer clkStableRst = unsafeFromLowPolarity clkStable1 - startFdecTestRst = unsafeFromLowPolarity startFdecTest - startFincTestRst = unsafeFromLowPolarity startFincTest - testRst = eitherReset clkStableRst (bothReset startFdecTestRst startFincTestRst) + anyStarted = fold (||) <$> startTests + testRst = orReset clkStableRst (unsafeFromLowPolarity anyStarted) testRstBool = unsafeToHighPolarity testRst (fInc, fDec) = fIncDec - testF = mux startFdecTest (pure Fdec) (pure Finc) + testF = fst . findWithDefault (FDec, True) snd . zip allTests <$> startTests (testResult, fIncDec, spiOut, debugSignals) = - fdecTestGo clk testRst clkControlled testF spiIn + goFincFdecTests clk testRst clkControlled testF spiIn (testDone, testSuccess) = unbundle $ testStateToDoneSuccess <$> testResult (spiBusy, spiState, siClkLocked, counterActive, counter) = debugSignals - (startFdecTest, startFincTest) = unbundle $ + startTests :: Signal Basic200A (Vec 4 Bool) + startTests = vioProbe ( "probe_test_done" :> "probe_test_success" @@ -199,8 +223,12 @@ fdecTest clkP clkN controlledClockP controlledClockN spiIn = :> "probe_fInc" :> "probe_fDec" :> Nil) - ("probe_test_start_fdec" :> "probe_test_start_finc" :> Nil) - (False, False) + ( "probe_test_start_fdec" + :> "probe_test_start_finc" + :> "probe_test_start_fdecfinc" + :> "probe_test_start_fincfdec" + :> Nil) + (repeat False) clk testDone testSuccess @@ -215,5 +243,5 @@ fdecTest clkP clkN controlledClockP controlledClockN spiIn = counter fInc fDec -{-# NOINLINE fdecTest #-} -makeTopEntity 'fdecTest +{-# NOINLINE fincFdecTests #-} +makeTopEntity 'fincFdecTests