Copyright | (C) 2013-2016 University of Twente 2016-2019 Myrtle Software Ltd 2017 Google Inc. 2021 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Extensions |
|
- Synchronous signals
- Domain
- Clock
- Reset
- Enabling
- Hidden clock, reset, and enable arguments
- Basic circuit functions
- Simulation and testbench functions
- Boolean connectives
- Product/Signal isomorphism
- Simulation functions (not synthesizable)
- List <-> Signal conversion (not synthesizable)
- QuickCheck combinators
- Type classes
- Bisignal functions
- Internals
Clash has synchronous Signal
s in the form of:
Signal
(dom ::Domain
) a
Where a is the type of the value of the Signal
, for example Int or Bool,
and dom is the clock- (and reset-) domain to which the memory elements
manipulating these Signal
s belong.
The type-parameter, dom, is of the kind Domain
- a simple string. That
string refers to a single synthesis domain. A synthesis domain describes the
behavior of certain aspects of memory elements in it. More specifically, a
domain looks like:
DomainConfiguration
{ _name ::Domain
-- ^ Domain name , _period ::Nat
-- ^ Clock period in ps , _activeEdge ::ActiveEdge
-- ^ Active edge of the clock , _resetKind ::ResetKind
-- ^ Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive) , _initBehavior ::InitBehavior
-- ^ Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value , _resetPolarity :: ResetPolarity -- ^ Whether resets are active high or active low }
Check the documentation of each of the types to see the various options Clash
provides. In order to specify a domain, an instance of KnownDomain
should be
made. Clash provides an implementation System
with some common options
chosen:
instance KnownDomain System where type KnownConf System = 'DomainConfiguration System 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh knownDomain = SDomainConfiguration SSymbol SNat SRising SAsynchronous SDefined SActiveHigh
In words, "System" is a synthesis domain with a clock running with a period of 10000 ps. Memory elements respond to the rising edge of the clock, asynchronously to changes in their resets, and have defined power up values if applicable.
In order to create a new domain, you don't have to instantiate it explicitly.
Instead, you can have createDomain
create a domain for you. You can also use
the same function to subclass existing domains.
- NB: "Bad things"™ happen when you actually use a clock period of
0
, so do not do that! - NB: You should be judicious using a clock with period of
1
as you can never create a clock that goes any faster! - NB: Whether
System
has good defaults depends on your target platform. Check outIntelSystem
andXilinxSystem
too!
Synopsis
- data Signal (dom :: Domain) a
- data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)
- data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)
- data BiSignalDefault
- type Domain = Symbol
- sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB)
- class KnownSymbol dom => KnownDomain (dom :: Domain) where
- type KnownConf dom :: DomainConfiguration
- knownDomain :: SDomainConfiguration dom (KnownConf dom)
- type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf)
- data ActiveEdge
- data SActiveEdge (edge :: ActiveEdge) where
- data InitBehavior
- data SInitBehavior (init :: InitBehavior) where
- data ResetKind
- data SResetKind (resetKind :: ResetKind) where
- data ResetPolarity
- data SResetPolarity (polarity :: ResetPolarity) where
- data DomainConfiguration = DomainConfiguration {}
- data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) where
- SDomainConfiguration :: SSymbol dom -> SNat period -> SActiveEdge edge -> SResetKind reset -> SInitBehavior init -> SResetPolarity polarity -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity)
- type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom)
- type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom)
- type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom)
- type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom)
- type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom)
- type System = "System" :: Domain
- type XilinxSystem = "XilinxSystem" :: Domain
- type IntelSystem = "IntelSystem" :: Domain
- vSystem :: VDomainConfiguration
- vIntelSystem :: VDomainConfiguration
- vXilinxSystem :: VDomainConfiguration
- data VDomainConfiguration = VDomainConfiguration {}
- vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration
- createDomain :: VDomainConfiguration -> Q [Dec]
- knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration
- clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period
- activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge
- resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync
- initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init
- resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity
- data Clock (dom :: Domain)
- periodToHz :: Natural -> Ratio Natural
- hzToPeriod :: HasCallStack => Ratio Natural -> Natural
- data Reset (dom :: Domain)
- unsafeToReset :: Signal dom Bool -> Reset dom
- unsafeFromReset :: Reset dom -> Signal dom Bool
- unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool
- unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool
- unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom
- unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom
- resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Reset dom
- resetGlitchFilter :: forall dom glitchlessPeriod n. (KnownDomain dom, glitchlessPeriod ~ (n + 1)) => SNat glitchlessPeriod -> Clock dom -> Reset dom -> Reset dom
- holdReset :: forall dom m. HiddenClockResetEnable dom => SNat m -> Reset dom
- data Enable dom
- toEnable :: Signal dom Bool -> Enable dom
- fromEnable :: Enable dom -> Signal dom Bool
- enableGen :: Enable dom
- type HiddenClock dom = (Hidden (HiddenClockName dom) (Clock dom), KnownDomain dom)
- hideClock :: forall dom r. HiddenClock dom => (Clock dom -> r) -> r
- exposeClock :: forall dom r. (HiddenClock dom => r) -> KnownDomain dom => Clock dom -> r
- withClock :: forall dom r. KnownDomain dom => Clock dom -> (HiddenClock dom => r) -> r
- hasClock :: forall dom. HiddenClock dom => Clock dom
- type HiddenReset dom = (Hidden (HiddenResetName dom) (Reset dom), KnownDomain dom)
- hideReset :: forall dom r. HiddenReset dom => (Reset dom -> r) -> r
- exposeReset :: forall dom r. (HiddenReset dom => r) -> KnownDomain dom => Reset dom -> r
- withReset :: forall dom r. KnownDomain dom => Reset dom -> (HiddenReset dom => r) -> r
- hasReset :: forall dom. HiddenReset dom => Reset dom
- type HiddenEnable dom = (Hidden (HiddenEnableName dom) (Enable dom), KnownDomain dom)
- hideEnable :: forall dom r. HiddenEnable dom => (Enable dom -> r) -> r
- exposeEnable :: forall dom r. (HiddenEnable dom => r) -> KnownDomain dom => Enable dom -> r
- withEnable :: forall dom r. KnownDomain dom => Enable dom -> (HiddenEnable dom => r) -> r
- hasEnable :: forall dom. HiddenEnable dom => Enable dom
- type HiddenClockResetEnable dom = (HiddenClock dom, HiddenReset dom, HiddenEnable dom)
- hideClockResetEnable :: forall dom r. HiddenClockResetEnable dom => (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r) -> r
- exposeClockResetEnable :: forall dom r. (HiddenClockResetEnable dom => r) -> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r
- withClockResetEnable :: forall dom r. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> (HiddenClockResetEnable dom => r) -> r
- type SystemClockResetEnable = (Hidden (HiddenClockName System) (Clock System), Hidden (HiddenResetName System) (Reset System), Hidden (HiddenEnableName System) (Enable System))
- andEnable :: forall dom r. HiddenEnable dom => Signal dom Bool -> (HiddenEnable dom => r) -> r
- dflipflop :: forall dom a. (HiddenClock dom, NFDataX a) => Signal dom a -> Signal dom a
- delay :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom a -> Signal dom a
- delayMaybe :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom (Maybe a) -> Signal dom a
- delayEn :: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) => a -> Signal dom Bool -> Signal dom a -> Signal dom a
- register :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom a -> Signal dom a
- regMaybe :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom (Maybe a) -> Signal dom a
- regEn :: forall dom a. (HiddenClockResetEnable dom, NFDataX a) => a -> Signal dom Bool -> Signal dom a -> Signal dom a
- mux :: Applicative f => f Bool -> f a -> f a -> f a
- clockGen :: KnownDomain dom => Clock dom
- resetGen :: forall dom. KnownDomain dom => Reset dom
- resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom
- systemClockGen :: Clock System
- systemResetGen :: Reset System
- (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool
- (.||.) :: Applicative f => f Bool -> f Bool -> f Bool
- class Bundle a where
- data EmptyTuple = EmptyTuple
- data TaggedEmptyTuple (dom :: Domain) = TaggedEmptyTuple
- simulate :: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b]
- simulateB :: forall dom a b. (KnownDomain dom, Bundle a, Bundle b, NFDataX a, NFDataX b) => (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) -> [a] -> [b]
- simulateN :: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) => Int -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b]
- simulateWithReset :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b]
- simulateWithResetN :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> Int -> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b]
- runUntil :: forall dom a. (KnownDomain dom, NFDataX a, ShowX a) => (a -> Bool) -> (HiddenClockResetEnable dom => Signal dom a) -> IO ()
- simulate_lazy :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> [a] -> [b]
- simulateB_lazy :: forall dom a b. (KnownDomain dom, Bundle a, Bundle b) => (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) -> [a] -> [b]
- signalAutomaton :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> Automaton (->) a b
- sample :: forall dom a. (KnownDomain dom, NFDataX a) => (HiddenClockResetEnable dom => Signal dom a) -> [a]
- sampleN :: forall dom a. (KnownDomain dom, NFDataX a) => Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a]
- sampleWithReset :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> (HiddenClockResetEnable dom => Signal dom a) -> [a]
- sampleWithResetN :: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) => SNat m -> Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a]
- fromList :: NFDataX a => [a] -> Signal dom a
- fromListWithReset :: forall dom a. (HiddenReset dom, NFDataX a) => a -> [a] -> Signal dom a
- sample_lazy :: forall dom a. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a) -> [a]
- sampleN_lazy :: forall dom a. KnownDomain dom => Int -> (HiddenClockResetEnable dom => Signal dom a) -> [a]
- fromList_lazy :: [a] -> Signal dom a
- testFor :: KnownDomain dom => Int -> (HiddenClockResetEnable dom => Signal dom Bool) -> Property
- (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
- (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
- (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n
- readFromBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d a
- writeToBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d (Maybe a) -> BiSignalOut ds d (BitSize a)
- mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m
- type HiddenClockName (dom :: Domain) = "clock"
- type HiddenResetName (dom :: Domain) = "reset"
- type HiddenEnableName (dom :: Domain) = "enable"
Synchronous signals
data Signal (dom :: Domain) a Source #
Clash has synchronous Signal
s in the form of:
Signal
(dom ::Domain
) a
Where a is the type of the value of the Signal
, for example Int or Bool,
and dom is the clock- (and reset-) domain to which the memory elements
manipulating these Signal
s belong.
The type-parameter, dom, is of the kind Domain
- a simple string. That
string refers to a single synthesis domain. A synthesis domain describes the
behavior of certain aspects of memory elements in it.
- NB: "Bad things"™ happen when you actually use a clock period of
0
, so do not do that! - NB: You should be judicious using a clock with period of
1
as you can never create a clock that goes any faster! - NB: For the best compatibility make sure your period is divisible by 2, because some VHDL simulators don't support fractions of picoseconds.
- NB: Whether
System
has good defaults depends on your target platform. Check outIntelSystem
andXilinxSystem
too!
Signals have the type role
>>>
:i Signal
type role Signal nominal representational ...
as it is safe to coerce the underlying value of a signal, but not safe to coerce a signal between different synthesis domains.
See the module documentation of Clash.Signal for more information about domains.
Instances
data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #
The in part of an inout port. BiSignalIn has the type role
>>>
:i BiSignalIn
type role BiSignalIn nominal nominal nominal ...
as it is not safe to coerce the default behaviour, synthesis domain or width of the data in the signal.
data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #
The out part of an inout port
Wraps (multiple) writing signals. The semantics are such that only one of the signals may write at a single time step.
BiSignalOut has the type role
>>>
:i BiSignalOut
type role BiSignalOut nominal nominal nominal ...
as it is not safe to coerce the default behaviour, synthesis domain or width of the data in the signal.
Instances
Semigroup (BiSignalOut defaultState dom n) Source # | NB Not synthesizable |
Defined in Clash.Signal.BiSignal (<>) :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n # sconcat :: NonEmpty (BiSignalOut defaultState dom n) -> BiSignalOut defaultState dom n # stimes :: Integral b => b -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n # | |
Monoid (BiSignalOut defaultState dom n) Source # | Monoid instance to support concatenating NB Not synthesizable |
Defined in Clash.Signal.BiSignal mempty :: BiSignalOut defaultState dom n # mappend :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n # mconcat :: [BiSignalOut defaultState dom n] -> BiSignalOut defaultState dom n # | |
type HasDomain dom1 (BiSignalOut ds dom2 n) Source # | |
Defined in Clash.Signal.BiSignal | |
type TryDomain t (BiSignalOut ds dom n) Source # | |
Defined in Clash.Signal.BiSignal |
data BiSignalDefault Source #
Used to specify the default behavior of a "BiSignal", i.e. what value is read when no value is being written to it.
PullUp | inout port behaves as if connected to a pull-up resistor |
PullDown | inout port behaves as if connected to a pull-down resistor |
Floating | inout port behaves as if is floating. Reading a floating "BiSignal" value in simulation will yield an errorX (undefined value). |
Instances
Show BiSignalDefault Source # | |
Defined in Clash.Signal.BiSignal showsPrec :: Int -> BiSignalDefault -> ShowS # show :: BiSignalDefault -> String # showList :: [BiSignalDefault] -> ShowS # |
Domain
sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB) Source #
We either get evidence that this function was instantiated with the same domains, or Nothing.
class KnownSymbol dom => KnownDomain (dom :: Domain) where Source #
A KnownDomain
constraint indicates that a circuit's behavior depends on
some properties of a domain. See DomainConfiguration
for more information.
type KnownConf dom :: DomainConfiguration Source #
knownDomain :: SDomainConfiguration dom (KnownConf dom) Source #
Returns SDomainConfiguration
corresponding to an instance's DomainConfiguration
.
Example usage:
>>>
knownDomain @System
SDomainConfiguration (SSymbol @"System") (SNat @10000) SRising SAsynchronous SDefined SActiveHigh
Instances
KnownDomain XilinxSystem Source # | System instance with defaults set for Xilinx FPGAs |
Defined in Clash.Signal.Internal type KnownConf XilinxSystem :: DomainConfiguration Source # | |
KnownDomain IntelSystem Source # | System instance with defaults set for Intel FPGAs |
Defined in Clash.Signal.Internal type KnownConf IntelSystem :: DomainConfiguration Source # | |
KnownDomain System Source # | A clock (and reset) dom with clocks running at 100 MHz |
Defined in Clash.Signal.Internal type KnownConf System :: DomainConfiguration Source # |
type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf) Source #
data ActiveEdge Source #
Determines clock edge memory elements are sensitive to. Not yet implemented.
Rising | Elements are sensitive to the rising edge (low-to-high) of the clock. |
Falling | Elements are sensitive to the falling edge (high-to-low) of the clock. |
Instances
data SActiveEdge (edge :: ActiveEdge) where Source #
Singleton version of ActiveEdge
SRising :: SActiveEdge 'Rising | |
SFalling :: SActiveEdge 'Falling |
Instances
Show (SActiveEdge edge) Source # | |
Defined in Clash.Signal.Internal showsPrec :: Int -> SActiveEdge edge -> ShowS # show :: SActiveEdge edge -> String # showList :: [SActiveEdge edge] -> ShowS # |
data InitBehavior Source #
Unknown | Power up value of memory elements is unknown. |
Defined | If applicable, power up value of a memory element is defined. Applies to
|
Instances
data SInitBehavior (init :: InitBehavior) where Source #
Instances
Show (SInitBehavior init) Source # | |
Defined in Clash.Signal.Internal showsPrec :: Int -> SInitBehavior init -> ShowS # show :: SInitBehavior init -> String # showList :: [SInitBehavior init] -> ShowS # |
Asynchronous | Elements respond asynchronously to changes in their reset input. This means that they do not wait for the next active clock edge, but respond immediately instead. Common on Intel FPGA platforms. |
Synchronous | Elements respond synchronously to changes in their reset input. This means that changes in their reset input won't take effect until the next active clock edge. Common on Xilinx FPGA platforms. |
Instances
Eq ResetKind Source # | |
Data ResetKind Source # | |
Defined in Clash.Signal.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResetKind -> c ResetKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResetKind # toConstr :: ResetKind -> Constr # dataTypeOf :: ResetKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ResetKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetKind) # gmapT :: (forall b. Data b => b -> b) -> ResetKind -> ResetKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResetKind -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResetKind -> r # gmapQ :: (forall d. Data d => d -> u) -> ResetKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ResetKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind # | |
Ord ResetKind Source # | |
Defined in Clash.Signal.Internal | |
Read ResetKind Source # | |
Show ResetKind Source # | |
Generic ResetKind Source # | |
NFData ResetKind Source # | |
Defined in Clash.Signal.Internal | |
Hashable ResetKind Source # | |
Defined in Clash.Signal.Internal | |
type Rep ResetKind Source # | |
data SResetKind (resetKind :: ResetKind) where Source #
Singleton version of ResetKind
Instances
Show (SResetKind reset) Source # | |
Defined in Clash.Signal.Internal showsPrec :: Int -> SResetKind reset -> ShowS # show :: SResetKind reset -> String # showList :: [SResetKind reset] -> ShowS # |
data ResetPolarity Source #
Determines the value for which a reset line is considered "active"
ActiveHigh | Reset is considered active if underlying signal is |
ActiveLow | Reset is considered active if underlying signal is |
Instances
data SResetPolarity (polarity :: ResetPolarity) where Source #
Singleton version of ResetPolarity
Instances
Show (SResetPolarity polarity) Source # | |
Defined in Clash.Signal.Internal showsPrec :: Int -> SResetPolarity polarity -> ShowS # show :: SResetPolarity polarity -> String # showList :: [SResetPolarity polarity] -> ShowS # |
data DomainConfiguration Source #
A domain with a name (Domain
). Configures the behavior of various aspects
of a circuits. See the documentation of this record's field types for more
information on the options.
See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.
DomainConfiguration | |
|
data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) where Source #
Singleton version of DomainConfiguration
SDomainConfiguration :: SSymbol dom -> SNat period -> SActiveEdge edge -> SResetKind reset -> SInitBehavior init -> SResetPolarity polarity -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity) |
Instances
Show (SDomainConfiguration dom conf) Source # | |
Defined in Clash.Signal.Internal showsPrec :: Int -> SDomainConfiguration dom conf -> ShowS # show :: SDomainConfiguration dom conf -> String # showList :: [SDomainConfiguration dom conf] -> ShowS # |
Configuration type families
type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom) Source #
Convenience type to help to extract a period from a domain. Example usage:
myFunc :: (KnownDomain dom, DomainPeriod dom ~ 6000) => ...
type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom) Source #
Convenience type to help to extract the active edge from a domain. Example usage:
myFunc :: (KnownDomain dom, DomainActiveEdge dom ~ 'Rising) => ...
type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom) Source #
Convenience type to help to extract the reset synchronicity from a domain. Example usage:
myFunc :: (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) => ...
type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom) Source #
Convenience type to help to extract the initial value behavior from a domain. Example usage:
myFunc :: (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) => ...
type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom) Source #
Convenience type to help to extract the reset polarity from a domain. Example usage:
myFunc :: (KnownDomain dom, DomainResetPolarity dom ~ 'ActiveHigh) => ...
Default domains
type System = "System" :: Domain Source #
A clock (and reset) dom with clocks running at 100 MHz. Memory elements respond to the rising edge of the clock, and asynchronously to changes in reset signals. It has defined initial values, and active-high resets.
See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.
type XilinxSystem = "XilinxSystem" :: Domain Source #
A clock (and reset) dom with clocks running at 100 MHz. Memory elements respond to the rising edge of the clock, and synchronously to changes in reset signals. It has defined initial values, and active-high resets.
See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.
type IntelSystem = "IntelSystem" :: Domain Source #
A clock (and reset) dom with clocks running at 100 MHz. Memory elements respond to the rising edge of the clock, and asynchronously to changes in reset signals. It has defined initial values, and active-high resets.
See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.
vSystem :: VDomainConfiguration Source #
Convenience value to allow easy "subclassing" of System domain. Should
be used in combination with createDomain
. For example, if you just want to
change the period but leave all other settings intact use:
createDomain vSystem{vName="System10", vPeriod=10}
vIntelSystem :: VDomainConfiguration Source #
Convenience value to allow easy "subclassing" of IntelSystem domain. Should
be used in combination with createDomain
. For example, if you just want to
change the period but leave all other settings intact use:
createDomain vIntelSystem{vName="Intel10", vPeriod=10}
vXilinxSystem :: VDomainConfiguration Source #
Convenience value to allow easy "subclassing" of XilinxSystem domain. Should
be used in combination with createDomain
. For example, if you just want to
change the period but leave all other settings intact use:
createDomain vXilinxSystem{vName="Xilinx10", vPeriod=10}
Domain utilities
data VDomainConfiguration Source #
Same as SDomainConfiguration but allows for easy updates through record update syntax.
Should be used in combination with vDomain
and createDomain
. Example:
createDomain (knownVDomain @System){vName="System10", vPeriod=10}
This duplicates the settings in the System
domain, replaces the name and
period, and creates an instance for it. As most users often want to update
the system domain, a shortcut is available in the form:
createDomain vSystem{vName="System10", vPeriod=10}
VDomainConfiguration | |
|
Instances
vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration Source #
Convert SDomainConfiguration
to VDomainConfiguration
. Should be used in combination with
createDomain
only.
createDomain :: VDomainConfiguration -> Q [Dec] Source #
Convenience method to express new domains in terms of others.
createDomain (knownVDomain @System){vName="System10", vPeriod=10}
This duplicates the settings in the System domain, replaces the name and period, and creates an instance for it. As most users often want to update the system domain, a shortcut is available in the form:
createDomain vSystem{vName="System10", vPeriod=10}
The function will create two extra identifiers. The first:
type System10 = ..
You can use that as the dom to Clocks/Resets/Enables/Signals. For example:
Signal System10 Int
. Additionally, it will create a VDomainConfiguration
that you can
use in later calls to createDomain
:
vSystem10 = knownVDomain @System10
It will also make System10
an instance of KnownDomain
.
If either identifier is already in scope it will not be generated a second time. Note: This can be useful for example when documenting a new domain:
-- | Here is some documentation for CustomDomain type CustomDomain = ("CustomDomain" :: Domain) -- | Here is some documentation for vCustomDomain createDomain vSystem{vName="CustomDomain"}
knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration Source #
Like 'knownDomain but yields a VDomainConfiguration
. Should only be used
in combination with createDomain
.
clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period Source #
Get the clock period from a KnownDomain context
activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge Source #
Get ActiveEdge
from a KnownDomain context. Example usage:
f :: forall dom . KnownDomain dom => .... f a b c = case activeEdge @dom of SRising -> foo SFalling -> bar
resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync Source #
Get ResetKind
from a KnownDomain context. Example usage:
f :: forall dom . KnownDomain dom => .... f a b c = case resetKind @dom of SAsynchronous -> foo SSynchronous -> bar
initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init Source #
Get InitBehavior
from a KnownDomain context. Example usage:
f :: forall dom . KnownDomain dom => .... f a b c = case initBehavior @dom of SDefined -> foo SUnknown -> bar
resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity Source #
Get ResetPolarity
from a KnownDomain context. Example usage:
f :: forall dom . KnownDomain dom => .... f a b c = case resetPolarity @dom of SActiveHigh -> foo SActiveLow -> bar
Clock
data Clock (dom :: Domain) Source #
A clock signal belonging to a domain named dom.
Instances
periodToHz :: Natural -> Ratio Natural Source #
Calculate the frequence in Hz, given the period in ps
i.e. to calculate the clock frequency of a clock with a period of 5000 ps:
>>>
periodToHz 5000
200000000 % 1
NB: This function is not synthesizable
hzToPeriod :: HasCallStack => Ratio Natural -> Natural Source #
Calculate the period, in ps, given a frequency in Hz
i.e. to calculate the clock period for a circuit to run at 240 MHz we get
>>>
hzToPeriod 240e6
4166
NB: This function is not synthesizable
NB: This function is lossy. I.e., periodToHz . hzToPeriod /= id.
Reset
data Reset (dom :: Domain) Source #
A reset signal belonging to a domain called dom.
The underlying representation of resets is Bool
.
unsafeToReset :: Signal dom Bool -> Reset dom Source #
unsafeToReset
is unsafe. For asynchronous resets it is unsafe
because it can introduce combinatorial loops. In case of synchronous resets
it can lead to meta-stability
issues in the presence of asynchronous resets.
NB: You probably want to use unsafeFromLowPolarity
or
unsafeFromHighPolarity
.
unsafeFromReset :: Reset dom -> Signal dom Bool Source #
unsafeFromReset
is unsafe because it can introduce:
For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.
NB: You probably want to use unsafeToLowPolarity
or
unsafeToHighPolarity
.
unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool Source #
Convert a reset to an active high reset. Has no effect if reset is already an active high reset. Is unsafe because it can introduce:
For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.
unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool Source #
Convert a reset to an active low reset. Has no effect if reset is already an active low reset. It is unsafe because it can introduce:
For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.
unsafeFromHighPolarity Source #
:: forall dom. KnownDomain dom | |
=> Signal dom Bool | Reset signal that's |
-> Reset dom |
Interpret a signal of bools as an active high reset and convert it to a reset signal corresponding to the domain's setting.
For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.
unsafeFromLowPolarity Source #
:: forall dom. KnownDomain dom | |
=> Signal dom Bool | Reset signal that's |
-> Reset dom |
Interpret a signal of bools as an active low reset and convert it to a reset signal corresponding to the domain's setting.
For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.
resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Reset dom Source #
The resetSynchronizer will synchronize an incoming reset according to whether the domain is synchronous or asynchronous.
For asynchronous resets this synchronizer ensures the reset will only be de-asserted synchronously but it can still be asserted asynchronously. The reset assert is immediate, but reset de-assertion is delayed by two cycles.
Normally, asynchronous resets can be both asynchronously asserted and
de-asserted. Asynchronous de-assertion can induce meta-stability in the
component which is being reset. To ensure this doesn't happen,
resetSynchronizer
ensures that de-assertion of a reset happens
synchronously. Assertion of the reset remains asynchronous.
Note that asynchronous assertion does not induce meta-stability in the component whose reset is asserted. However, when a component "A" in another clock or reset domain depends on the value of a component "B" being reset, then asynchronous assertion of the reset of component "B" can induce meta-stability in component "A". To prevent this from happening you need to use a proper synchronizer, for example one of the synchronizers in Clash.Explicit.Synchronizer.
For synchronous resets this function ensures that the reset is asserted and de-asserted synchronously. Both the assertion and de-assertion of the reset are delayed by two cycles.
Example 1
The circuit below detects a rising bit (i.e., a transition from 0 to 1) in a
given argument. It takes a reset that is not synchronized to any of the other
incoming signals and synchronizes it using resetSynchronizer
.
topEntity
:: Clock System
-> Reset System
-> Signal System Bit
-> Signal System (BitVector 8)
topEntity clk asyncRst key1 =
withClockResetEnable clk rst enableGen leds
where
rst = resetSynchronizer
clk asyncRst
key1R = isRising 1 key1
leds = mealy blinkerT (1, False, 0) key1R
Example 2
Similar to Example 1 this circuit detects a rising bit (i.e., a transition from 0 to 1) in a given argument. It takes a clock that is not stable yet and a reset singal that is not synchronized to any other signals. It stabalizes the clock and then synchronizes the reset signal.
topEntity
:: Clock System
-> Reset System
-> Signal System Bit
-> Signal System (BitVector 8)
topEntity clk rst key1 =
let (pllOut,pllStable) = altpll (SSymbol @"altpll50") clk rst
rstSync = resetSynchronizer
pllOut (unsafeToHighPolarity pllStable)
in exposeClockResetEnable leds pllOut rstSync enableGen
where
key1R = isRising 1 key1
leds = mealy blinkerT (1, False, 0) key1R
Implementation details
resetSynchronizer
implements the following circuit for asynchronous domains:
rst --------------------------------------+ | | +----v----+ +----v----+ deasserted | | | | ---------------> +-------> +--------> | | | | +---|> | +---|> | | | | | | | | +---------+ | +---------+ clk | | -----------------------------+
This corresponds to figure 3d at https://www.embedded.com/asynchronous-reset-synchronization-and-distribution-challenges-and-solutions/
For synchronous domains two sequential dflipflops are used:
+---------+ +---------+ rst | | | | ---------------> +-------> +--------> | | | | +---|> | +---|> | | | | | | | | +---------+ | +---------+ clk | | -----------------------------+
:: forall dom glitchlessPeriod n. (KnownDomain dom, glitchlessPeriod ~ (n + 1)) | |
=> SNat glitchlessPeriod | Consider a reset signal to be properly asserted after having seen the reset asserted for glitchlessPeriod cycles straight. |
-> Clock dom | |
-> Reset dom | |
-> Reset dom |
Filter glitches from reset signals by only triggering a reset after it has been asserted for glitchlessPeriod cycles. It will then stay asserted for as long as the given reset was asserted consecutively.
If synthesized on a domain with initial values, resetGlitchFilter
will
output an asserted reset for glitchlessPeriod cycles (plus any cycles added
by the given reset). If initial values can't be used, it will only output
defined reset values after glitchlessPeriod cycles.
Example 1
>>>
let sampleResetN n = sampleN n . unsafeToHighPolarity
>>>
let resetFromList = unsafeFromHighPolarity . fromList
>>>
let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True]
>>>
sampleResetN 12 (resetGlitchFilter d2 systemClockGen rst)
[True,True,True,True,False,False,False,False,False,True,True,False]
:: forall dom m. HiddenClockResetEnable dom | |
=> SNat m | Hold for m cycles, counting from the moment the incoming reset signal becomes deasserted. |
-> Reset dom |
Hold reset for a number of cycles relative to an implicit reset signal.
Example:
>>>
sampleN @System 8 (unsafeToHighPolarity (holdReset (SNat @2)))
[True,True,True,False,False,False,False,False]
holdReset
holds the reset for an additional 2 clock cycles for a total
of 3 clock cycles where the reset is asserted.
Enabling
A signal of booleans, indicating whether a component is enabled. No special meaning is implied, it's up to the component itself to decide how to respond to its enable line. It is used throughout Clash as a global enable signal.
fromEnable :: Enable dom -> Signal dom Bool Source #
Convert Enable
construct to its underlying representation: a signal of
bools.
Hidden clock, reset, and enable arguments
Clocks, resets and enables are by default implicitly routed to their components. You can see from the type of a component whether it has hidden clock, reset or enable arguments:
It has a hidden clock when it has a:
f :: HiddenClock
dom => ...
Constraint.
Or it has a hidden reset when it has a:
g :: HiddenReset
dom => ...
Constraint.
Or it has a hidden enable when it has a:
g :: HiddenEnable
dom => ...
Constraint.
Or it has a hidden clock argument, a hidden reset argument and a hidden enable argument when it has a:
h :: HiddenClockResetEnable
dom => ..
Constraint.
Given a component with explicit clock, reset and enable arguments, you can turn
them into hidden arguments using hideClock
, hideReset
, and hideEnable
. So
given a:
f :: Clock dom -> Reset dom -> Enable dom -> Signal dom a -> ...
You hide the clock and reset arguments by:
-- g ::HiddenClockResetEnable
dom => Signal dom a -> ... g =hideClockResetEnable
f
Or, alternatively, by:
-- h ::HiddenClockResetEnable
dom => Signal dom a -> ... h = fhasClock
hasReset
hasEnable
Assigning explicit clock, reset and enable arguments to hidden clocks, resets and enables
Given a component:
f :: HiddenClockResetEnable
dom
=> Signal dom Int
-> Signal dom Int
which has hidden clock, reset and enable arguments, we expose those hidden arguments so that we can explicitly apply them:
-- g :: Clock dom -> Reset dom -> Enable dom -> Signal dom Int -> Signal dom Int
g = exposeClockResetEnable
f
or, alternatively, by:
-- h :: Clock dom -> Reset dom -> Enable dom -> Signal dom Int -> Signal dom Int
h clk rst en = withClockResetEnable
clk rst en f
Similarly, there are exposeClock
, exposeReset
and exposeEnable
to just
expose the hidden clock, the hidden reset or the hidden enable argument.
You will need to explicitly apply clocks and resets when you want to use
components such as PLLs and resetSynchronizer
:
topEntity :: Clock System -> Reset System -> Signal System Bit -> Signal System (BitVector 8) topEntity clk rst key1 = let (pllOut,pllStable) =altpll
(SSymbol @"altpll50") clk rst rstSync =resetSynchronizer
pllOut (unsafeToHighPolarity pllStable) inexposeClockResetEnable
leds pllOut rstSync enableGen where key1R = isRising 1 key1 leds = mealy blinkerT (1, False, 0) key1R
or, using the alternative method:
topEntity :: Clock System -> Reset System -> Signal System Bit -> Signal System (BitVector 8) topEntity clk rst key1 = let (pllOut,pllStable) =altpll
(SSymbol @"altpll50") clk rst rstSync =resetSynchronizer
pllOut (unsafeToHighPolarity pllStable) inwithClockResetEnable
pllOut rstSync enableGen leds where key1R = isRising 1 key1 leds = mealy blinkerT (1, False, 0) key1R
Monomorphism restriction leads to surprising behavior
If you don't provide a type signature for a function, Haskell will infer one for you. Sometimes this inferred type is less general than you would expect. This can be due to the monomorphism restriction, which is a rather intricate technical aspect of Haskell's type system. You don't need to understand it to avoid the problems it creates with hidden parameters, though.
The expose...
and with...
functions for hidden clocks, resets, and enables
are intended to be used to resolve a function with hidden parameters into a
function without that hidden parameter. Put differently, exposeClock
and
withClock
are not themselves used in a HiddenClock
context, and so on for
resets and enables. If the rule that they are not themselves in a Hidden...
context is observed, they will function as expected. No specific consideration
is needed in these cases.
However, the function andEnable
is explicitly designed to be used within a
HiddenEnable
context. In such a situation, it is important to provide a type
signature for the component that is given to andEnable
as an argument, and not
let Haskell infer one.
The use of andEnable
has an unfortunate interaction with Haskells monomorphism
restriction that can lead to very surprising behavior. All of the following also
applies to using exposeClock
and withClock
inside a HiddenClock
context,
and so on for resets and enables.
When you write a function
f :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i -- BROKEN where g = register 0
you would intuitively think this has the following type for the local function g
:
f :: forall dom . HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i where g :: HiddenClockResetEnable dom => Signal dom Int -> Signal dom Int g = register 0
but instead, the monomorphism restriction will cause the following type to be inferred:
f :: forall dom . HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i -- BROKEN where g :: Signal dom Int -> Signal dom Int g = register 0
The monomorphism restriction essentially misqualifies the implicit parameter as
polymorphism, and tries to remove the implicit parameter from the context of the
function's type. It can do that because the outer scope already has a
HiddenEnable
context. But by getting that implicit parameter of the enclosing
function as context, it also gets the value of the parameter of the enclosing
function. So the Enable line for g
is the Enable line of f
, and the Enable
line produced by andEnable
that was intended to be connected to g
is not
connected to anything!
When using andEnable
, you should always explicitly provide the type signature
for the component given to andEnable
as an argument, thereby avoiding
surprising inferred types. We don't advise you to turn off the monomorphism
restriction, as this may have undesirable consequences.
Note that the inferred type is not always incorrect. The following variant works correctly:
f :: HiddenClockResetEnable dom => Signal dom Bool -> Signal dom Int -> Signal dom Int f en i = andEnable en g i where g i = register 0 i
This is an instance of the very first example on
HaskellWiki, f1
(as
opposed to f4
). The monomorphism restriction works differently for function
bindings and pattern bindings. Since g
here has a formal parameter, it is a
function binding, and the monomorphish restriction does not kick in. The code
works as expected. If a later code change removes the formal parameter, all of a
sudden the code silently disregards the en
signal! Adhering to the rule that
you should always explicitly provide the type signature for the component given
to andEnable
as an argument would have avoided this hard to debug problem.
Hidden clock
type HiddenClock dom = (Hidden (HiddenClockName dom) (Clock dom), KnownDomain dom) Source #
A constraint that indicates the component has a hidden Clock
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. HiddenClock dom | |
=> (Clock dom -> r) | Function whose clock argument you want to hide |
-> r |
Hide the Clock
argument of a component, so it can be routed implicitly.
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. (HiddenClock dom => r) | The component with a hidden clock |
-> KnownDomain dom => Clock dom -> r | The component with its clock argument exposed |
Expose a hidden Clock
argument of a component, so it can be applied
explicitly.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeClock reg clockGen
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force exposeClock
to work on System
(hence sampleN
not needing an explicit
domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeClock @System reg clockGen
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
:: forall dom r. KnownDomain dom | |
=> Clock dom | The |
-> (HiddenClock dom => r) | The function with a hidden |
-> r |
Connect an explicit Clock
to a function with a hidden Clock
.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = withClock clockGen reg
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force withClock
to work on System
(hence sampleN
not needing an explicit
domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = withClock @System clockGen reg
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
hasClock :: forall dom. HiddenClock dom => Clock dom Source #
Connect a hidden Clock
to an argument where a normal Clock
argument
was expected.
Click here to read more about hidden clocks, resets, and enables
Hidden reset
type HiddenReset dom = (Hidden (HiddenResetName dom) (Reset dom), KnownDomain dom) Source #
A constraint that indicates the component needs a Reset
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. HiddenReset dom | |
=> (Reset dom -> r) | Component whose reset argument you want to hide |
-> r |
Hide the Reset
argument of a component, so it can be routed implicitly.
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. (HiddenReset dom => r) | The component with a hidden reset |
-> KnownDomain dom => Reset dom -> r | The component with its reset argument exposed |
Expose a hidden Reset
argument of a component, so it can be applied
explicitly.
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeReset reg resetGen
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force exposeReset
to work on System
(hence sampleN
not needing an explicit
domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeReset @System reg resetGen
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
:: forall dom r. KnownDomain dom | |
=> Reset dom | The |
-> (HiddenReset dom => r) | The function with a hidden |
-> r |
Connect an explicit Reset
to a function with a hidden Reset
.
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = withReset resetGen reg
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force withReset
to work on System
(hence sampleN
not needing an explicit
domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = withReset @System resetGen reg
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
hasReset :: forall dom. HiddenReset dom => Reset dom Source #
Connect a hidden Reset
to an argument where a normal Reset
argument
was expected.
Click here to read more about hidden clocks, resets, and enables
Hidden enable
type HiddenEnable dom = (Hidden (HiddenEnableName dom) (Enable dom), KnownDomain dom) Source #
A constraint that indicates the component needs an Enable
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. HiddenEnable dom | |
=> (Enable dom -> r) | Component whose enable argument you want to hide |
-> r |
Hide the Enable
argument of a component, so it can be routed implicitly.
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. (HiddenEnable dom => r) | The component with a hidden enable |
-> KnownDomain dom => Enable dom -> r | The component with its enable argument exposed |
Expose a hidden Enable
argument of a component, so it can be applied
explicitly.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeEnable reg enableGen
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force exposeEnable
to work on System
(hence sampleN
not needing an
explicit domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeEnable @System reg enableGen
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
:: forall dom r. KnownDomain dom | |
=> Enable dom | The |
-> (HiddenEnable dom => r) | The function with a hidden |
-> r |
Connect an explicit Enable
to a function with a hidden Enable
.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = withEnable enableGen reg
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force withEnable
to work on System
(hence sampleN
not needing an explicit
domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = withEnable @System enableGen reg
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
hasEnable :: forall dom. HiddenEnable dom => Enable dom Source #
Connect a hidden Enable
to an argument where a normal Enable
argument
was expected.
Click here to read more about hidden clocks, resets, and enables
Hidden clock, reset, and enable
type HiddenClockResetEnable dom = (HiddenClock dom, HiddenReset dom, HiddenEnable dom) Source #
A constraint that indicates the component needs a Clock
, a Reset
,
and an Enable
belonging to the same dom
.
Click here to read more about hidden clocks, resets, and enables
:: forall dom r. HiddenClockResetEnable dom | |
=> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r) | Component whose clock, reset, and enable argument you want to hide |
-> r |
Hide the Clock
, Reset
, and Enable
arguments of a component, so they
can be routed implicitly.
Click here to read more about hidden clocks, resets, and enables
exposeClockResetEnable Source #
:: forall dom r. (HiddenClockResetEnable dom => r) | The component with hidden clock, reset, and enable arguments |
-> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r | The component with its clock, reset, and enable arguments exposed |
Expose hidden Clock
, Reset
, and Enable
arguments of a component, so
they can be applied explicitly.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeClockResetEnable reg clockGen resetGen enableGen
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force exposeClockResetEnable
to work on System
(hence sampleN
not needing
an explicit domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = exposeClockResetEnable @System reg clockGen resetGen enableGen
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
Usage in a testbench context:
topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8) topEntity = concat testBench :: Signal System Bool testBench = done where testInput = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil) expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil) done = exposeClockResetEnable (expectedOutput (topEntity <$> testInput)) clk rst en clk = tbSystemClockGen (not <$> done) rst = systemResetGen en = enableGen
:: forall dom r. KnownDomain dom | |
=> Clock dom | The |
-> Reset dom | The |
-> Enable dom | The |
-> (HiddenClockResetEnable dom => r) | The function with a hidden |
-> r |
Connect an explicit Clock
, Reset
, and Enable
to a function with a
hidden Clock
, Reset
, and Enable
.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
sig = withClockResetEnable clockGen resetGen enableGen reg
>>>
sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]
Force withClockResetEnable
to work on System
(hence sampleN
not needing
an explicit domain later):
>>>
reg = register 5 (reg + 1)
>>>
sig = withClockResetEnable @System clockGen resetGen enableGen reg
>>>
sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]
type SystemClockResetEnable = (Hidden (HiddenClockName System) (Clock System), Hidden (HiddenResetName System) (Reset System), Hidden (HiddenEnableName System) (Enable System)) Source #
A constraint that indicates the component needs a Clock
, a Reset
,
and an Enable
belonging to the System
domain.
Click here to read more about hidden clocks, resets, and enables
Basic circuit functions
:: forall dom r. HiddenEnable dom | |
=> Signal dom Bool | The signal to AND with |
-> (HiddenEnable dom => r) | The component whose enable is modified |
-> r |
Merge enable signal with signal of bools by applying the boolean AND operation.
NB: The component given to andEnable
as an argument needs an explicit type signature.
Please read Monomorphism restriction leads to surprising
behavior.
The component whose enable is modified will only be enabled when both the
encompassing HiddenEnable
and the Signal
dom
Bool
are asserted.
Click here to read more about hidden clocks, resets, and enables
Example
Usage with a polymorphic domain:
>>>
reg = register 5 (reg + 1)
>>>
f en = andEnable en reg
>>>
sampleN @System 10 (f (riseEvery d2))
[5,5,5,6,6,7,7,8,8,9]
Force andEnable
to work on System
(hence sampleN
not needing an explicit
domain later):
>>>
reg = register 5 (reg + 1)
>>>
f en = andEnable @System en reg
>>>
sampleN 10 (f (riseEvery d2))
[5,5,5,6,6,7,7,8,8,9]
dflipflop :: forall dom a. (HiddenClock dom, NFDataX a) => Signal dom a -> Signal dom a Source #
Special version of delay
that doesn't take enable signals of any kind.
Initial value will be undefined.
:: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) | |
=> a | Initial value |
-> Signal dom a | Signal to delay |
-> Signal dom a |
:: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) | |
=> a | Initial value |
-> Signal dom (Maybe a) | |
-> Signal dom a |
:: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) | |
=> a | Initial value |
-> Signal dom Bool | Enable |
-> Signal dom a | |
-> Signal dom a |
Version of delay
that only updates when its second argument is asserted.
>>>
let input = fromList [1,2,3,4,5,6,7::Int]
>>>
let enable = fromList [True,True,False,False,True,True,True]
>>>
sampleN @System 7 (delayEn 0 enable input)
[0,1,2,2,2,5,6]
:: forall dom a. (HiddenClockResetEnable dom, NFDataX a) | |
=> a | Reset value. |
-> Signal dom a | |
-> Signal dom a |
:: forall dom a. (HiddenClockResetEnable dom, NFDataX a) | |
=> a | Reset value. |
-> Signal dom (Maybe a) | |
-> Signal dom a |
Version of register
that only updates its content when its second
argument is a Just
value. So given:
sometimes1 = s where s =register
Nothing (switch<$>
s) switch Nothing = Just 1 switch _ = Nothing countSometimes = s where s =regMaybe
0 (plusM (pure
<$>
s) sometimes1) plusM =liftA2
(liftA2 (+))
We get:
>>>
sampleN @System 9 sometimes1
[Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]>>>
sampleN @System 9 countSometimes
[0,0,0,1,1,2,2,3,3]
:: forall dom a. (HiddenClockResetEnable dom, NFDataX a) | |
=> a | Reset value. |
-> Signal dom Bool | |
-> Signal dom a | |
-> Signal dom a |
Version of register
that only updates its content when its second argument
is asserted. So given:
oscillate =register
False (not
<$>
oscillate) count =regEn
0 oscillate (count + 1)
We get:
>>>
sampleN @System 9 oscillate
[False,False,True,False,True,False,True,False,True]>>>
sampleN @System 9 count
[0,0,0,1,1,2,2,3,3]
mux :: Applicative f => f Bool -> f a -> f a -> f a Source #
Simulation and testbench functions
clockGen :: KnownDomain dom => Clock dom Source #
Clock generator for simulations. Do not use this clock generator for
the testBench function, use tbClockGen
instead.
To be used like:
clkSystem = clockGen @System
See DomainConfiguration
for more information on how to use synthesis domains.
resetGen :: forall dom. KnownDomain dom => Reset dom Source #
:: forall dom n. (KnownDomain dom, 1 <= n) | |
=> SNat n | Number of initial cycles to hold reset high |
-> Reset dom |
Generate reset that's asserted for the first n cycles.
To be used like:
rstSystem5 = resetGen System (SNat
5)
Example usage:
>>>
sampleN 7 (unsafeToHighPolarity (resetGenN @System (SNat @3)))
[True,True,True,False,False,False,False]
systemClockGen :: Clock System Source #
Clock generator for the System
clock domain.
NB: should only be used for simulation, and not for the testBench
function. For the testBench function, used tbSystemClockGen
systemResetGen :: Reset System Source #
Reset generator for the System
clock domain.
NB: should only be used for simulation or the testBench function.
Example
topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
topEntity = concat
testBench :: Signal System Bool
testBench = done
where
testInput = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
done = exposeClockResetEnable (expectedOutput (topEntity $ testInput)) clk rst
clk = tbSystemClockGen (not <$> done)
rst = systemResetGen
Boolean connectives
Product/Signal isomorphism
Isomorphism between a Signal
of a product type (e.g. a tuple) and a
product type of Signal
s.
Instances of Bundle
must satisfy the following laws:
bundle
.unbundle
=id
unbundle
.bundle
=id
By default, bundle
and unbundle
, are defined as the identity, that is,
writing:
data D = A | B instance Bundle D
is the same as:
data D = A | B instance Bundle D where typeUnbundled
clk D =Signal
clk Dbundle
s = sunbundle
s = s
For custom product types you'll have to write the instance manually:
data Pair a b = MkPair { getA :: a, getB :: b } instance Bundle (Pair a b) where type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b) -- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b) bundle (MkPair as bs) = MkPair $ as * bs -- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b) unbundle pairs = MkPair (getA $ pairs) (getB $ pairs)
Nothing
bundle :: Unbundled dom a -> Signal dom a Source #
Example:
bundle :: (Signal
dom a,Signal
dom b) ->Signal
dom (a,b)
However:
bundle ::Signal
domBit
->Signal
domBit
Instances
Bundle Bool Source # | |
Bundle Double Source # | |
Bundle Float Source # | |
Bundle Int Source # | |
Bundle Integer Source # | |
Bundle () Source # | |
Bundle Bit Source # | |
Bundle EmptyTuple Source # | See commit 94b0bff5
and documentation for |
Defined in Clash.Signal.Bundle type Unbundled dom EmptyTuple = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom EmptyTuple -> Signal dom EmptyTuple Source # unbundle :: forall (dom :: Domain). Signal dom EmptyTuple -> Unbundled dom EmptyTuple Source # | |
Bundle (Maybe a) Source # | |
Bundle (BitVector n) Source # | |
Bundle (Index n) Source # | |
Bundle (Unsigned n) Source # | |
Bundle (Signed n) Source # | |
Bundle (Either a b) Source # | |
Bundle (a1, a2) Source # | |
KnownNat n => Bundle (Vec n a) Source # | |
KnownNat d => Bundle (RTree d a) Source # | |
Bundle (a1, a2, a3) Source # | N.B.: The documentation only shows instances up to 3-tuples. By
default, instances up to and including 12-tuples will exist. If the flag
|
Bundle (Fixed rep int frac) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle ((f :*: g) a) Source # | |
data EmptyTuple Source #
See TaggedEmptyTuple
Instances
Bundle EmptyTuple Source # | See commit 94b0bff5
and documentation for |
Defined in Clash.Signal.Bundle type Unbundled dom EmptyTuple = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom EmptyTuple -> Signal dom EmptyTuple Source # unbundle :: forall (dom :: Domain). Signal dom EmptyTuple -> Unbundled dom EmptyTuple Source # | |
Bundle EmptyTuple Source # | See commit 94b0bff5
and documentation for |
Defined in Clash.Signal.Delayed.Bundle type Unbundled dom d EmptyTuple = (res :: Type) Source # bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d EmptyTuple -> DSignal dom d EmptyTuple Source # unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d EmptyTuple -> Unbundled dom d EmptyTuple Source # | |
type Unbundled dom EmptyTuple Source # | |
Defined in Clash.Signal.Bundle | |
type Unbundled dom d EmptyTuple Source # | |
Defined in Clash.Signal.Delayed.Bundle |
data TaggedEmptyTuple (dom :: Domain) Source #
Helper type to emulate the "old" behavior of Bundle's unit instance. I.e.,
the instance for Bundle ()
used to be defined as:
class Bundle () where bundle :: () -> Signal dom () unbundle :: Signal dom () -> ()
In order to have sensible type inference, the Bundle
class specifies that
the argument type of bundle
should uniquely identify the result type, and
vice versa for unbundle
. The type signatures in the snippet above don't
though, as ()
doesn't uniquely map to a specific domain. In other words,
domain
should occur in both the argument and result of both functions.
TaggedEmptyTuple
tackles this by carrying the domain in its type. The
bundle
and unbundle
instance now looks like:
class Bundle EmptyTuple where bundle :: TaggedEmptyTuple dom -> Signal dom EmptyTuple unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom
dom
is now mentioned both the argument and result for both bundle
and
unbundle
.
Simulation functions (not synthesizable)
:: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) | |
=> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) | Circuit to simulate, whose source potentially has a hidden clock, reset, and/or enable. |
-> [a] | |
-> [b] |
Simulate a (
) function given a list of samples
of type aSignal
a -> Signal
b
>>>
simulate @System (register 8) [1, 2, 3]
[8,1,2,3... ...
Where System
denotes the domain to simulate on. The reset line is
asserted for a single cycle. The first value is therefore supplied twice to
the circuit: once while reset is high, and once directly after. The first
output value (the value produced while the reset is asserted) is dropped.
If you only want to simulate a finite number of samples, see simulateN
. If
you need the reset line to be asserted for more than one cycle or if you
need a custom reset value, see simulateWithReset
and simulateWithResetN
.
NB: This function is not synthesizable
:: forall dom a b. (KnownDomain dom, Bundle a, Bundle b, NFDataX a, NFDataX b) | |
=> (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) | Function we want to simulate, whose components potentially have a hidden clock (and reset) |
-> [a] | |
-> [b] |
:: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) | |
=> Int | Number of cycles to simulate (excluding cycle spent in reset) |
-> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) |
|
-> [a] | |
-> [b] |
Same as simulate
, but only sample the first Int output values.
NB: This function is not synthesizable
:: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) | |
=> SNat m | Number of cycles to assert the reset |
-> a | Reset value |
-> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) |
|
-> [a] | |
-> [b] |
Same as simulate
, but with the reset line asserted for n cycles. Similar
to simulate
, simulateWithReset
will drop the output values produced while
the reset is asserted. While the reset is asserted, the reset value a is
supplied to the circuit.
:: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) | |
=> SNat m | Number of cycles to assert the reset |
-> a | Reset value |
-> Int | Number of cycles to simulate (excluding cycles spent in reset) |
-> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) |
|
-> [a] | |
-> [b] |
Same as simulateWithReset
, but only sample the first Int output values.
:: forall dom a. (KnownDomain dom, NFDataX a, ShowX a) | |
=> (a -> Bool) | Condition checking function, should return |
-> (HiddenClockResetEnable dom => Signal dom a) |
|
-> IO () |
Simulate a component until it matches a condition
If the given component has not yet been given a clock, reset, or enable
line, runUntil
will supply them. The reset will be asserted for a single
cycle.
It prints a message of the form
Signal sampled for N cycles until value X
NB: This function is not synthesizable
Example with test bench
A common usage is with a test bench using
outputVerifier
.
NB: Since this uses assert
, when using
clashi
, read the note at Clash.Explicit.Testbench.
import Clash.Prelude import Clash.Explicit.Testbench topEntity ::Signal
System
Int ->Signal
System
Int topEntity = id testBench ::Signal
System
Bool testBench = done where testInput =stimuliGenerator
clk rst $(listToVecTH
[1 :: Int .. 10]) expectedOutput =outputVerifier'
clk rst $(listToVecTH
$ [1 :: Int .. 9]<>
[42]) done = expectedOutput $ topEntity testInput clk =tbSystemClockGen
(not <$> done) rst =systemResetGen
> runUntil id testBench cycle(<Clock: System>): 10, outputVerifier expected value: 42, not equal to actual value: 10 Signal sampled for 11 cycles until value True
When you need to verify multiple test benches, the following invocations come in handy:
> mapM_
(runUntil id) [ testBenchA, testBenchB ]
or when the test benches are in different clock domains:
testBenchA :: Signal DomA Bool testBenchB :: Signal DomB Bool
> sequence_
[ runUntil id testBenchA, runUntil id testBenchB ]
lazy versions
:: forall dom a b. KnownDomain dom | |
=> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) | Function we want to simulate, whose components potentially have a hidden clock (and reset) |
-> [a] | |
-> [b] |
:: forall dom a b. (KnownDomain dom, Bundle a, Bundle b) | |
=> (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b) | Function we want to simulate, whose components potentially have a hidden clock (and reset) |
-> [a] | |
-> [b] |
Automaton
signalAutomaton :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> Automaton (->) a b Source #
List <-> Signal conversion (not synthesizable)
:: forall dom a. (KnownDomain dom, NFDataX a) | |
=> (HiddenClockResetEnable dom => Signal dom a) |
|
-> [a] |
Get an infinite list of samples from a Signal
The elements in the list correspond to the values of the Signal
at consecutive clock cycles
sample s == [s0, s1, s2, s3, ...
If the given component has not yet been given a clock, reset, or enable
line, sample
will supply them. The reset will be asserted for a single
cycle. sample
will not drop the value produced by the circuit while
the reset was asserted. If you want this, or if you want more than a
single cycle reset, consider using sampleWithReset
.
NB: This function is not synthesizable
:: forall dom a. (KnownDomain dom, NFDataX a) | |
=> Int | Number of samples to produce |
-> (HiddenClockResetEnable dom => Signal dom a) |
|
-> [a] |
Get a list of n samples from a Signal
The elements in the list correspond to the values of the Signal
at consecutive clock cycles
sampleN @System 3 s == [s0, s1, s2]
If the given component has not yet been given a clock, reset, or enable
line, sampleN
will supply them. The reset will be asserted for a single
cycle. sampleN
will not drop the value produced by the circuit while
the reset was asserted. If you want this, or if you want more than a
single cycle reset, consider using sampleWithResetN
.
NB: This function is not synthesizable
:: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) | |
=> SNat m | Number of cycles to assert the reset |
-> (HiddenClockResetEnable dom => Signal dom a) |
|
-> [a] |
Get an infinite list of samples from a Signal
, while asserting the reset
line for m clock cycles. sampleWithReset
does not return the first m
cycles, i.e., when the reset is asserted.
NB: This function is not synthesizable
:: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) | |
=> SNat m | Number of cycles to assert the reset |
-> Int | Number of samples to produce |
-> (HiddenClockResetEnable dom => Signal dom a) |
|
-> [a] |
Get a list of n samples from a Signal
, while asserting the reset line
for m clock cycles. sampleWithReset
does not return the first m cycles,
i.e., while the reset is asserted.
NB: This function is not synthesizable
fromList :: NFDataX a => [a] -> Signal dom a Source #
Create a Signal
from a list
Every element in the list will correspond to a value of the signal for one clock cycle.
>>>
sampleN 2 (fromList [1,2,3,4,5])
[1,2]
NB: This function is not synthesizable
fromListWithReset :: forall dom a. (HiddenReset dom, NFDataX a) => a -> [a] -> Signal dom a Source #
Like fromList
, but resets on reset and has a defined reset value.
>>>
let rst = unsafeFromHighPolarity (fromList [True, True, False, False, True, False])
>>>
let res = withReset rst (fromListWithReset Nothing [Just 'a', Just 'b', Just 'c'])
>>>
sampleN @System 6 res
[Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
NB: This function is not synthesizable
lazy versions
:: forall dom a. KnownDomain dom | |
=> (HiddenClockResetEnable dom => Signal dom a) |
|
-> [a] |
Lazily get an infinite list of samples from a Signal
The elements in the list correspond to the values of the Signal
at consecutive clock cycles
sample s == [s0, s1, s2, s3, ...
If the given component has not yet been given a clock, reset, or enable
line, sample_lazy
will supply them. The reset will be asserted for a
single cycle. sample_lazy
will not drop the value produced by the
circuit while the reset was asserted.
NB: This function is not synthesizable
:: forall dom a. KnownDomain dom | |
=> Int | |
-> (HiddenClockResetEnable dom => Signal dom a) |
|
-> [a] |
Lazily get a list of n samples from a Signal
The elements in the list correspond to the values of the Signal
at consecutive clock cycles
sampleN @System 3 s == [s0, s1, s2]
If the given component has not yet been given a clock, reset, or enable
line, sampleN_lazy
will supply them. The reset will be asserted for a
single cycle. sampleN_lazy
will not drop the value produced by the
circuit while the reset was asserted.
NB: This function is not synthesizable
fromList_lazy :: [a] -> Signal dom a Source #
Create a Signal
from a list
Every element in the list will correspond to a value of the signal for one clock cycle.
>>>
sampleN 2 (fromList [1,2,3,4,5] :: Signal System Int)
[1,2]
NB: This function is not synthesizable
QuickCheck combinators
:: KnownDomain dom | |
=> Int | The number of cycles we want to test for |
-> (HiddenClockResetEnable dom => Signal dom Bool) |
|
-> Property |
testFor n s
tests the signal s for n cycles.
NB: This function is not synthesizable
Type classes
Eq
-like
Ord
-like
Bisignal functions
veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n Source #
Converts the out
part of a BiSignal to an in
part. In simulation it
checks whether multiple components are writing and will error accordingly.
Make sure this is only called ONCE for every BiSignal.
:: (HasCallStack, BitPack a) | |
=> BiSignalIn ds d (BitSize a) | A |
-> Signal d a |
Read the value from an inout port
:: (HasCallStack, BitPack a) | |
=> BiSignalIn ds d (BitSize a) | |
-> Signal d (Maybe a) | Value to write
|
-> BiSignalOut ds d (BitSize a) |
Write to an inout port
mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m Source #
Combine several inout signals into one.
Internals
type HiddenClockName (dom :: Domain) = "clock" Source #
type HiddenResetName (dom :: Domain) = "reset" Source #
type HiddenEnableName (dom :: Domain) = "enable" Source #