@@ -237,6 +237,7 @@ module Clash.Explicit.Signal
237237 , register
238238 , regMaybe
239239 , regEn
240+ , regEnN
240241 , mux
241242 , apWhen
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,35 @@ regEn = \clk rst gen initial en i ->
760762 register# clk rst (andEnable gen en) initial initial i
761763{-# INLINE regEn #-}
762764
765+ -- | A simple queuing FIFO that pushes data through whenever the
766+ -- enable input line is high. Hence, with every new input the output
767+ -- at the end of the queue gets updated. Technically, this is nothing
768+ -- else than a chain of 'regEn's.
769+ regEnN ::
770+ forall dom a n .
771+ (KnownDomain dom , NFDataX a ) =>
772+ Clock dom ->
773+ -- ^ Clock
774+ Reset dom ->
775+ -- ^ Reset, 'regEnN' outputs the reset value when the reset value is active
776+ Enable dom ->
777+ -- ^ Global enable
778+ SNat n ->
779+ -- ^ size of FIFO / number of stored elements
780+ a ->
781+ -- ^ initial content of the FIFO
782+ Signal dom Bool ->
783+ -- ^ "push next input" indicator
784+ Signal dom a ->
785+ -- ^ input stream
786+ Signal dom a
787+ -- ^ final FIFO element
788+ regEnN clk rst gen n@ SNat initial en = case compareSNat n (SNat @ 0 ) of
789+ SNatLE -> id
790+ SNatGT -> regEn clk rst gen initial en
791+ . leToPlus @ 1 @ n (regEnN clk rst gen (predSNat n) initial en)
792+ {-# INLINE regEnN #-}
793+
763794-- * Simulation functions
764795
765796-- | Same as 'simulate', but with the reset line asserted for /n/ cycles. Similar
0 commit comments