Skip to content

Commit 09fc1a6

Browse files
committed
Add regEnN
1 parent 5c09f91 commit 09fc1a6

File tree

2 files changed

+61
-1
lines changed

2 files changed

+61
-1
lines changed

clash-prelude/src/Clash/Explicit/Signal.hs

Lines changed: 32 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -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)
301302
import GHC.TypeLits (type (<=))
302303

303304
import Clash.Annotations.Primitive (hasBlackBox)
304-
import Clash.Promoted.Nat (SNat(..), snatToNum)
305+
import Clash.Promoted.Nat
306+
(SNat(..), SNatLE(..), compareSNat, leToPlus, predSNat, snatToNum)
305307
import Clash.Signal.Bundle
306308
(Bundle (..), EmptyTuple(..), TaggedEmptyTuple(..), vecBundle#)
307309
import 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

clash-prelude/src/Clash/Signal.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -201,6 +201,7 @@ module Clash.Signal
201201
, register
202202
, regMaybe
203203
, regEn
204+
, regEnN
204205
, mux
205206
, apWhen
206207
-- * Simulation and testbench functions
@@ -1202,6 +1203,34 @@ regEn = \initial en i ->
12021203
i
12031204
{-# INLINE regEn #-}
12041205

1206+
-- | A simple queuing FIFO that pushes data through whenever the
1207+
-- enable input line is high. Hence, with every new input the output
1208+
-- at the end of the queue gets updated. Technically, this is nothing
1209+
-- else than a chain of 'regEn's.
1210+
regEnN ::
1211+
forall dom a n.
1212+
(HiddenClockResetEnable dom, NFDataX a) =>
1213+
SNat n ->
1214+
-- ^ size of FIFO / number of stored elements
1215+
a ->
1216+
-- ^ initial content of the FIFO
1217+
Signal dom Bool ->
1218+
-- ^ "push next input" indicator
1219+
Signal dom a ->
1220+
-- ^ input stream
1221+
Signal dom a
1222+
-- ^ final FIFO element
1223+
regEnN = \sn initial en i ->
1224+
E.regEnN
1225+
(fromLabel @(HiddenClockName dom))
1226+
(fromLabel @(HiddenResetName dom))
1227+
(fromLabel @(HiddenEnableName dom))
1228+
sn
1229+
initial
1230+
en
1231+
i
1232+
{-# INLINE regEnN #-}
1233+
12051234
-- * Signal -> List conversion
12061235

12071236
-- | Get an infinite list of samples from a 'Signal'

0 commit comments

Comments
 (0)