Skip to content

Commit

Permalink
Move block RAM reset value into the ClearOnReset constructor of `Re…
Browse files Browse the repository at this point in the history
…setStrategy`,

to avoid arguments that are only going to be ignored on `NoClearOnReset`
  • Loading branch information
gergoerdi committed Nov 29, 2024
1 parent f13b853 commit 1481dc1
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 24 deletions.
1 change: 1 addition & 0 deletions changelog/2024-11-25T20_38_27+08_00_reset_strategy
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
CHANGED: `ResetStrategy` now contains the reset function, to avoid dummy arguments on `NoClearOnReset`
28 changes: 13 additions & 15 deletions clash-prelude/src/Clash/Explicit/BlockRam.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand All @@ -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
Expand All @@ -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
Expand Down Expand Up @@ -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.
Expand All @@ -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 ->
Expand Down
10 changes: 4 additions & 6 deletions clash-prelude/src/Clash/Prelude/BlockRam.hs
Original file line number Diff line number Diff line change
Expand Up @@ -741,23 +741,21 @@ 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))
-- ^ (write address @w@, value to write)
-> 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
Expand 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.
Expand Down
3 changes: 1 addition & 2 deletions tests/shouldwork/Signal/BlockRam0.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion tests/shouldwork/Signal/BlockRam1.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ topEntity = exposeClockResetEnable go where
go rd wr = zeroAt0 dout where
dout =
blockRam1
ClearOnReset
(ClearOnReset ())
(SNat @1024)
(3 :: Unsigned 8)
rd
Expand Down

0 comments on commit 1481dc1

Please sign in to comment.