@@ -237,6 +237,7 @@ module Clash.Explicit.Signal
237237 , register
238238 , regMaybe
239239 , regEn
240+ , regEnN
240241 , mux
241242 , apEn
242243 -- * Simulation and testbench functions
@@ -301,7 +302,8 @@ import Data.Maybe (isJust)
301302import GHC.TypeLits (type (<= ))
302303
303304import Clash.Annotations.Primitive (hasBlackBox )
304- import Clash.Promoted.Nat (SNat (.. ), snatToNum )
305+ import Clash.Promoted.Nat
306+ (SNat (.. ), SNatLE (.. ), compareSNat , leToPlus , predSNat , snatToNum )
305307import Clash.Signal.Bundle
306308 (Bundle (.. ), EmptyTuple (.. ), TaggedEmptyTuple (.. ), vecBundle #)
307309import Clash.Signal.BiSignal
@@ -760,6 +762,30 @@ regEn = \clk rst gen initial en i ->
760762 register# clk rst (andEnable gen en) initial initial i
761763{-# INLINE regEn #-}
762764
765+ -- | A chain of 'regEn's.
766+ regEnN ::
767+ forall dom a n .
768+ (KnownDomain dom , NFDataX a ) =>
769+ -- | Clock
770+ Clock dom ->
771+ -- | Reset, 'regEnN' outputs the reset value when the reset value is active
772+ Reset dom ->
773+ -- | Global enable
774+ Enable dom ->
775+ -- | The number of stored elements
776+ SNat n ->
777+ -- | Initial content of all elements in the chain.
778+ a ->
779+ -- | The "push next input" indicator
780+ Signal dom Bool ->
781+ Signal dom a ->
782+ Signal dom a
783+ regEnN clk rst gen n@ SNat initial en = case compareSNat n (SNat @ 0 ) of
784+ SNatLE -> id
785+ SNatGT -> regEn clk rst gen initial en
786+ . leToPlus @ 1 @ n (regEnN clk rst gen (predSNat n) initial en)
787+ {-# INLINE regEnN #-}
788+
763789-- * Simulation functions
764790
765791-- | Same as 'simulate', but with the reset line asserted for /n/ cycles. Similar
0 commit comments