diff --git a/changelog/2025-10-03T10_14_19+02_00_add_convenience_primitives b/changelog/2025-10-03T10_14_19+02_00_add_convenience_primitives new file mode 100644 index 0000000000..20565451c7 --- /dev/null +++ b/changelog/2025-10-03T10_14_19+02_00_add_convenience_primitives @@ -0,0 +1 @@ +ADDED: `apEn`, and `regEnN`. diff --git a/clash-prelude/src/Clash/Explicit/Signal.hs b/clash-prelude/src/Clash/Explicit/Signal.hs index 3f707fc4ef..8744ff0476 100644 --- a/clash-prelude/src/Clash/Explicit/Signal.hs +++ b/clash-prelude/src/Clash/Explicit/Signal.hs @@ -3,7 +3,7 @@ Copyright : (C) 2013-2016, University of Twente, 2016-2019, Myrtle Software, 2017-2022, Google Inc. 2020 , Ben Gamari, - 2021-2024, QBayLogic B.V. + 2021-2025, QBayLogic B.V. License : BSD2 (see the file LICENSE) Maintainer : QBayLogic B.V. @@ -237,7 +237,9 @@ module Clash.Explicit.Signal , register , regMaybe , regEn + , regEnN , mux + , apEn -- * Simulation and testbench functions , clockGen , resetGen @@ -300,7 +302,8 @@ import Data.Maybe (isJust) import GHC.TypeLits (type (<=)) import Clash.Annotations.Primitive (hasBlackBox) -import Clash.Promoted.Nat (SNat(..), snatToNum) +import Clash.Promoted.Nat + (SNat(..), SNatLE(..), compareSNat, leToPlus, snatToNum) import Clash.Signal.Bundle (Bundle (..), EmptyTuple(..), TaggedEmptyTuple(..), vecBundle#) import Clash.Signal.BiSignal @@ -759,6 +762,31 @@ regEn = \clk rst gen initial en i -> register# clk rst (andEnable gen en) initial initial i {-# INLINE regEn #-} +-- | A chain of 'regEn's. +regEnN :: + forall dom a n. + (KnownDomain dom, NFDataX a) => + -- | Clock + Clock dom -> + -- | Reset, 'regEnN' outputs the reset value when the reset value is active + Reset dom -> + -- | Global enable + Enable dom -> + -- | The number of stored elements + SNat n -> + -- | Initial content of all elements in the chain. + a -> + -- | The "push next input" indicator + Signal dom Bool -> + Signal dom a -> + Signal dom a +regEnN clk rst gen n@SNat initial en = case compareSNat n (SNat @0) of + SNatLE -> id + SNatGT -> leToPlus @1 @n + $ Clash.Sized.Vector.last + . Clash.Sized.Vector.generate n (regEn clk rst gen initial en) +{-# INLINE regEnN #-} + -- * Simulation functions -- | Same as 'simulate', but with the reset line asserted for /n/ cycles. Similar diff --git a/clash-prelude/src/Clash/Signal.hs b/clash-prelude/src/Clash/Signal.hs index 2e6b9566a6..fa2d6dbea5 100644 --- a/clash-prelude/src/Clash/Signal.hs +++ b/clash-prelude/src/Clash/Signal.hs @@ -2,7 +2,7 @@ Copyright : (C) 2013-2016, University of Twente, 2016-2019, Myrtle Software Ltd, 2017 , Google Inc., - 2021-2024, QBayLogic B.V. + 2021-2025, QBayLogic B.V. License : BSD2 (see the file LICENSE) Maintainer : QBayLogic B.V. @@ -201,7 +201,9 @@ module Clash.Signal , register , regMaybe , regEn + , regEnN , mux + , apEn -- * Simulation and testbench functions , clockGen , resetGen @@ -1201,6 +1203,29 @@ regEn = \initial en i -> i {-# INLINE regEn #-} +-- | A chain of 'regEn's. +regEnN :: + forall dom a n. + (HiddenClockResetEnable dom, NFDataX a) => + -- | The number of stored elements + SNat n -> + -- | Initial content of all elements in the chain. + a -> + -- | The "push next input" indicator + Signal dom Bool -> + Signal dom a -> + Signal dom a +regEnN = \sn initial en i -> + E.regEnN + (fromLabel @(HiddenClockName dom)) + (fromLabel @(HiddenResetName dom)) + (fromLabel @(HiddenEnableName dom)) + sn + initial + en + i +{-# INLINE regEnN #-} + -- * Signal -> List conversion -- | Get an infinite list of samples from a 'Signal' diff --git a/clash-prelude/src/Clash/Signal/Internal.hs b/clash-prelude/src/Clash/Signal/Internal.hs index 76108c5450..0773aaf4aa 100644 --- a/clash-prelude/src/Clash/Signal/Internal.hs +++ b/clash-prelude/src/Clash/Signal/Internal.hs @@ -126,6 +126,7 @@ module Clash.Signal.Internal , syncRegister# , registerPowerup# , mux + , apEn -- * Simulation and testbench functions , clockGen , tbClockGen @@ -1653,6 +1654,13 @@ mux :: Applicative f => f Bool -> f a -> f a -> f a mux = liftA3 (\b t f -> if b then t else f) {-# INLINE mux #-} +-- | A 'mux' extension muxing between a given argument and an updated version. +-- Given @apEn b f s@, output an updated version of @s@ (i.e., @f s@) +-- when @b@ is 'True', but return it unchanged (i.e., @s@) when @b@ is 'False'. +apEn :: Applicative f => f Bool -> (a -> a) -> f a -> f a +apEn cond upd x = mux cond (upd <$> x) x +{-# INLINE apEn #-} + infix 4 .==. -- | The above type is a generalization for: --