diff --git a/changelog/2024-11-25T20_38_27+08_00_reset_strategy b/changelog/2024-11-25T20_38_27+08_00_reset_strategy new file mode 100644 index 0000000000..0347059a1b --- /dev/null +++ b/changelog/2024-11-25T20_38_27+08_00_reset_strategy @@ -0,0 +1 @@ +CHANGED: `ResetStrategy` now contains the reset function, to avoid dummy arguments on `NoClearOnReset` diff --git a/clash-prelude/src/Clash/Explicit/BlockRam.hs b/clash-prelude/src/Clash/Explicit/BlockRam.hs index a52084fbe9..91df7e4491 100644 --- a/clash-prelude/src/Clash/Explicit/BlockRam.hs +++ b/clash-prelude/src/Clash/Explicit/BlockRam.hs @@ -854,9 +854,9 @@ blockRamPow2 = \clk en cnt rd wrM -> withFrozenCallStack (blockRam clk en cnt rd wrM) {-# INLINE blockRamPow2 #-} -data ResetStrategy (r :: Bool) where - ClearOnReset :: ResetStrategy 'True - NoClearOnReset :: ResetStrategy 'False +data ResetStrategy (r :: Bool) a where + ClearOnReset :: a -> ResetStrategy 'True a + NoClearOnReset :: ResetStrategy 'False a -- | A version of 'blockRam' that has no default values set. May be cleared to -- an arbitrary state using a reset function. @@ -875,25 +875,28 @@ blockRamU -- for the BRAM to be reset to its initial state. -> Enable dom -- ^ 'Enable' line - -> ResetStrategy r + -> ResetStrategy r (Index n -> a) -- ^ Whether to clear BRAM on asserted reset ('ClearOnReset') or -- not ('NoClearOnReset'). The reset needs to be asserted for at least /n/ -- cycles to clear the BRAM. -> SNat n -- ^ Number of elements in BRAM - -> (Index n -> a) - -- ^ If applicable (see 'ResetStrategy' argument), reset BRAM using this function -> Signal dom addr -- ^ Read address @r@ -> Signal dom (Maybe (addr, a)) -- ^ (write address @w@, value to write) -> Signal dom a -- ^ Value of the BRAM at address @r@ from the previous clock cycle -blockRamU clk rst0 en rstStrategy n@SNat initF rd0 mw0 = +blockRamU clk rst0 en rstStrategy n@SNat rd0 mw0 = case rstStrategy of - ClearOnReset -> + ClearOnReset initF -> -- Use reset infrastructure blockRamU# clk en n rd1 we1 wa1 w1 + where + rd1 = mux rstBool 0 (fromEnum <$> rd0) + we1 = mux rstBool (pure True) we0 + wa1 = mux rstBool (fromInteger . toInteger <$> waCounter) (fromEnum <$> wa0) + w1 = mux rstBool (initF <$> waCounter) w0 NoClearOnReset -> -- Ignore reset infrastructure, pass values unchanged blockRamU# clk en n @@ -912,11 +915,6 @@ blockRamU clk rst0 en rstStrategy n@SNat initF rd0 mw0 = w0 = snd . fromJustX <$> mw0 we0 = isJust <$> mw0 - rd1 = mux rstBool 0 (fromEnum <$> rd0) - we1 = mux rstBool (pure True) we0 - wa1 = mux rstBool (fromInteger . toInteger <$> waCounter) (fromEnum <$> wa0) - w1 = mux rstBool (initF <$> waCounter) w0 - -- | blockRAMU primitive blockRamU# :: forall n dom a @@ -968,7 +966,7 @@ blockRam1 -- for the BRAM to be reset to its initial state. -> Enable dom -- ^ 'Enable' line - -> ResetStrategy r + -> ResetStrategy r () -- ^ Whether to clear BRAM on asserted reset ('ClearOnReset') or -- not ('NoClearOnReset'). The reset needs to be asserted for at least /n/ -- cycles to clear the BRAM. @@ -984,7 +982,7 @@ blockRam1 -- ^ Value of the BRAM at address @r@ from the previous clock cycle blockRam1 clk rst0 en rstStrategy n@SNat a rd0 mw0 = case rstStrategy of - ClearOnReset -> + ClearOnReset () -> -- Use reset infrastructure blockRam1# clk en n a rd1 we1 wa1 w1 NoClearOnReset -> diff --git a/clash-prelude/src/Clash/Prelude/BlockRam.hs b/clash-prelude/src/Clash/Prelude/BlockRam.hs index db58c6d3c7..744af158d5 100644 --- a/clash-prelude/src/Clash/Prelude/BlockRam.hs +++ b/clash-prelude/src/Clash/Prelude/BlockRam.hs @@ -741,14 +741,12 @@ blockRamU , Enum addr , NFDataX addr , 1 <= n ) - => E.ResetStrategy r + => E.ResetStrategy r (Index n -> a) -- ^ Whether to clear BRAM on asserted reset ('Clash.Explicit.BlockRam.ClearOnReset') -- or not ('Clash.Explicit.BlockRam.NoClearOnReset'). The reset needs to be -- asserted for at least /n/ cycles to clear the BRAM. -> SNat n -- ^ Number of elements in BRAM - -> (Index n -> a) - -- ^ If applicable (see first argument), reset BRAM using this function -> Signal dom addr -- ^ Read address @r@ -> Signal dom (Maybe (addr, a)) @@ -756,8 +754,8 @@ blockRamU -> Signal dom a -- ^ Value of the BRAM at address @r@ from the previous clock cycle blockRamU = - \rstStrategy cnt initF rd wrM -> withFrozenCallStack - (hideClockResetEnable E.blockRamU) rstStrategy cnt initF rd wrM + \rstStrategy cnt rd wrM -> withFrozenCallStack + (hideClockResetEnable E.blockRamU) rstStrategy cnt rd wrM {-# INLINE blockRamU #-} -- | A version of 'blockRam' that is initialized with the same value on all @@ -770,7 +768,7 @@ blockRam1 , Enum addr , NFDataX addr , 1 <= n ) - => E.ResetStrategy r + => E.ResetStrategy r () -- ^ Whether to clear BRAM on asserted reset ('Clash.Explicit.BlockRam.ClearOnReset') -- or not ('Clash.Explicit.BlockRam.NoClearOnReset'). The reset needs to be -- asserted for at least /n/ cycles to clear the BRAM. diff --git a/tests/shouldwork/Signal/BlockRam0.hs b/tests/shouldwork/Signal/BlockRam0.hs index 7c01fd0cdf..51553dc846 100644 --- a/tests/shouldwork/Signal/BlockRam0.hs +++ b/tests/shouldwork/Signal/BlockRam0.hs @@ -29,9 +29,8 @@ topEntity = exposeClockResetEnable go where go rd wr = zeroAt0 dout where dout = blockRamU - ClearOnReset + (ClearOnReset ((+22) . unpack . pack :: Index 1024 -> Unsigned 10)) (SNat @1024) - ((+22) . unpack . pack :: Index 1024 -> Unsigned 10) rd wr -- See: https://github.com/clash-lang/clash-compiler/pull/2511 diff --git a/tests/shouldwork/Signal/BlockRam1.hs b/tests/shouldwork/Signal/BlockRam1.hs index 3ff38a51e9..981981d95d 100644 --- a/tests/shouldwork/Signal/BlockRam1.hs +++ b/tests/shouldwork/Signal/BlockRam1.hs @@ -29,7 +29,7 @@ topEntity = exposeClockResetEnable go where go rd wr = zeroAt0 dout where dout = blockRam1 - ClearOnReset + (ClearOnReset ()) (SNat @1024) (3 :: Unsigned 8) rd