clash-prelude-1.7.0: Clash: a functional hardware description language - Prelude library
Copyright(C) 2020-2023 QBayLogic B.V.
2022-2023 Google LLC
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Explicit.Reset

Contents

Description

Utilities to deal with resets.

Synopsis

Documentation

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

Expand

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

Expand

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 signal that is not synchronized to any other signals. It stabilizes the clock and then synchronizes the reset signal.

Note that the function altpllSync provides this functionality in a convenient form, obviating the need for resetSynchronizer for this use case.

topEntity
  :: Clock  System
  -> Reset  System
  -> Signal System Bit
  -> Signal System (BitVector 8)
topEntity clk rst key1 =
    let  (pllOut,pllStable) = unsafeAltpll clk rst
         rstSync            = resetSynchronizer pllOut (unsafeFromActiveLow pllStable)
    in   exposeClockResetEnable leds pllOut rstSync enableGen
  where
    key1R  = isRising 1 key1
    leds   = mealy blinkerT (1, False, 0) key1R

Implementation details

Expand

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     |                 |
  -----------------------------+

resetGlitchFilter Source #

Arguments

:: forall dom glitchlessPeriod. (HasCallStack, HasDefinedInitialValues dom, 1 <= glitchlessPeriod) 
=> 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. Similarly, it will stay asserted until a glitchlessPeriod number of deasserted cycles have been observed.

This circuit can only be used on platforms supporting initial values. This restriction can be worked around by using unsafeResetGlitchFilter but this is not recommended.

On platforms without initial values, you should instead use resetGlitchFilterWithReset with an additional power-on reset, or holdReset if filtering is only needed on deassertion.

At power-on, the reset will be asserted. If the filtered reset input remains unasserted, the output reset will deassert after glitchlessPeriod clock cycles.

If resetGlitchFilter is used in a domain with asynchronous resets (Asynchronous), resetGlitchFilter will first synchronize the reset input with dualFlipFlopSynchronizer.

Example 1

Expand
>>> let sampleResetN n = sampleN n . unsafeToActiveHigh
>>> let resetFromList = unsafeFromActiveHigh . fromList
>>> let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True, True]
>>> sampleResetN 12 (resetGlitchFilter d2 (clockGen @XilinxSystem) rst)
[True,True,True,True,False,False,False,False,False,True,True,True]

resetGlitchFilterWithReset Source #

Arguments

:: forall dom glitchlessPeriod. (HasCallStack, KnownDomain dom, 1 <= glitchlessPeriod) 
=> SNat glitchlessPeriod

Consider a reset signal to be properly asserted after having seen the reset asserted for glitchlessPeriod cycles straight.

-> Clock dom 
-> Reset dom

The power-on reset for the glitch filter itself

-> Reset dom

The reset that will be filtered

-> Reset dom 

Filter glitches from reset signals by only triggering a reset after it has been asserted for glitchlessPeriod cycles. Similarly, it will stay asserted until a glitchlessPeriod number of deasserted cycles have been observed.

Compared to resetGlitchFilter, this function adds an additional power-on reset input. As soon as the power-on reset asserts, the reset output will assert, and after the power-on reset deasserts, the reset output will stay asserted for another glitchlessPeriod clock cycles. This is identical behavior to holdReset where it concerns the power-on reset, and differs from the filtered reset, which will only cause an assertion after glitchlessPeriod cycles.

If resetGlitchFilterWithReset is used in a domain with asynchronous resets (Asynchronous), resetGlitchFilterWithReset will first synchronize the reset input with dualFlipFlopSynchronizer.

unsafeResetGlitchFilter Source #

Arguments

:: forall dom glitchlessPeriod. (HasCallStack, KnownDomain dom, 1 <= glitchlessPeriod) 
=> 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. Similarly, it will stay asserted until a glitchlessPeriod number of deasserted cycles have been observed.

On platforms without initial values (Unknown), resetGlitchFilter cannot be used and you should use resetGlitchFilterWithReset with an additional power-on reset, or holdReset if filtering is only needed on deassertion.

unsafeResetGlitchFilter allows breaking the requirement of initial values, but by doing so it is possible that the design starts up with a period of up to 2 * glitchlessPeriod clock cycles where the reset output is unasserted (or longer in the case of glitches on the filtered reset input). This can cause a number of problems. The outputs/tri-states of the design might output random things, including coherent but incorrect streams of data. This might have grave repercussions in the design's environment (sending network packets, overwriting non-volatile memory, in extreme cases destroying controlled equipment or causing harm to living beings, ...).

Without initial values, the synthesized result of unsafeResetGlitchFilter eventually correctly outputs a filtered version of the reset input. However, in simulation, it will indefinitely output an undefined value. This happens both in Clash simulation and in HDL simulation. Therefore, simulation should not include the unsafeResetGlitchFilter.

If unsafeResetGlitchFilter is used in a domain with asynchronous resets (Asynchronous), unsafeResetGlitchFilter will first synchronize the reset input with dualFlipFlopSynchronizer.

holdReset Source #

Arguments

:: forall dom n. KnownDomain dom 
=> Clock dom 
-> Enable dom

Global enable

-> SNat n

Hold for n cycles, counting from the moment the incoming reset signal becomes deasserted.

-> Reset dom

Reset to extend

-> Reset dom 

Hold reset for a number of cycles relative to an incoming reset signal.

Example:

>>> let sampleWithReset = sampleN 8 . unsafeToActiveHigh
>>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (resetGenN (SNat @3)))
[True,True,True,True,True,False,False,False]

holdReset holds the reset for an additional 2 clock cycles for a total of 5 clock cycles where the reset is asserted. holdReset also works on intermediate assertions of the reset signal:

>>> let rst = fromList [True, False, False, False, True, False, False, False]
>>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (unsafeFromActiveHigh rst))
[True,True,True,False,True,True,True,False]

convertReset :: forall domA domB. (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> Reset domA -> Reset domB Source #

Convert between different types of reset, adding a synchronizer when the domains are not the same. See resetSynchronizer for further details about reset synchronization.

If domA has Synchronous resets, a flip-flop is inserted in domA to filter glitches. This adds one domA clock cycle delay.

noReset :: KnownDomain dom => Reset dom Source #

A reset that is never asserted

andReset :: forall dom. HasSynchronousReset dom => Reset dom -> Reset dom -> Reset dom Source #

Output reset will be asserted when both input resets are asserted

unsafeAndReset :: forall dom. KnownDomain dom => Reset dom -> Reset dom -> Reset dom Source #

Output reset will be asserted when both input resets are asserted. This function is considered unsafe because it can be used on domains with components with asynchronous resets, where use of this function can introduce glitches triggering a reset.

orReset :: forall dom. HasSynchronousReset dom => Reset dom -> Reset dom -> Reset dom Source #

Output reset will be asserted when either one of the input resets is asserted

unsafeOrReset :: forall dom. KnownDomain dom => Reset dom -> Reset dom -> Reset dom Source #

Output reset will be asserted when either one of the input resets is asserted. This function is considered unsafe because it can be used on domains with components with asynchronous resets, where use of this function can introduce glitches triggering a reset.

data Reset (dom :: Domain) Source #

A reset signal belonging to a domain called dom.

The underlying representation of resets is Bool.

Instances

Instances details
ClocksSync (Clock c1, Reset c1) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksSyncClocksInst (Clock c1, Reset c1) domIn Source #

type ClocksResetSynchronizerCxt (Clock c1, Reset c1) Source #

Methods

clocksResetSynchronizer :: forall (domIn :: Domain). (KnownDomain domIn, ClocksResetSynchronizerCxt (Clock c1, Reset c1)) => ClocksSyncClocksInst (Clock c1, Reset c1) domIn -> Clock domIn -> (Clock c1, Reset c1) Source #

ClocksSync (Clock c1, Reset c1, Clock c2, Reset c2) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2) domIn Source #

type ClocksResetSynchronizerCxt (Clock c1, Reset c1, Clock c2, Reset c2) Source #

Methods

clocksResetSynchronizer :: forall (domIn :: Domain). (KnownDomain domIn, ClocksResetSynchronizerCxt (Clock c1, Reset c1, Clock c2, Reset c2)) => ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2) domIn -> Clock domIn -> (Clock c1, Reset c1, Clock c2, Reset c2) Source #

ClocksSync (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) domIn Source #

type ClocksResetSynchronizerCxt (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) Source #

Methods

clocksResetSynchronizer :: forall (domIn :: Domain). (KnownDomain domIn, ClocksResetSynchronizerCxt (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3)) => ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) domIn -> Clock domIn -> (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) Source #

type HasDomain dom1 (Reset dom2) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSpecificDomain

type HasDomain dom1 (Reset dom2) = DomEq dom1 dom2
type TryDomain t (Reset dom) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type TryDomain t (Reset dom) = 'Found dom
type ClocksResetSynchronizerCxt (Clock c1, Reset c1) Source # 
Instance details

Defined in Clash.Clocks

type ClocksSyncClocksInst (Clock c1, Reset c1) domIn Source # 
Instance details

Defined in Clash.Clocks

type ClocksSyncClocksInst (Clock c1, Reset c1) domIn = (Clock c1, Signal domIn Bool)
type ClocksResetSynchronizerCxt (Clock c1, Reset c1, Clock c2, Reset c2) Source # 
Instance details

Defined in Clash.Clocks

type ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2) domIn Source # 
Instance details

Defined in Clash.Clocks

type ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2) domIn = (Clock c1, Clock c2, Signal domIn Bool)
type ClocksResetSynchronizerCxt (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) Source # 
Instance details

Defined in Clash.Clocks

type ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) domIn Source # 
Instance details

Defined in Clash.Clocks

type ClocksSyncClocksInst (Clock c1, Reset c1, Clock c2, Reset c2, Clock c3, Reset c3) domIn = (Clock c1, Clock c2, Clock c3, Signal domIn Bool)

resetGen :: forall dom. KnownDomain dom => Reset dom Source #

Reset generator for simulation purposes. Asserts the reset for a single cycle.

To be used like:

rstSystem = resetGen @System

See tbClockGen for example usage.

NB: While this can be used in the testBench function, it cannot be synthesized to hardware.

resetGenN Source #

Arguments

:: forall dom n. (KnownDomain dom, 1 <= n) 
=> SNat n

Number of initial cycles to hold reset high

-> Reset dom 

Reset generator for simulation purposes. Asserts the reset for the first n cycles.

To be used like:

rstSystem5 = resetGen @System d5

Example usage:

>>> sampleN 7 (unsafeToActiveHigh (resetGenN @System d3))
[True,True,True,False,False,False,False]

NB: While this can be used in the testBench function, it cannot be synthesized to hardware.

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

systemResetGen :: Reset System Source #

Reset generator for use in simulation, for the System clock domain. Asserts the reset for a single cycle.

NB: While this can be used in the testBench function, it cannot be synthesized to hardware.

Example

Expand
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

unsafeToReset :: KnownDomain dom => 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 unsafeFromActiveLow or unsafeFromActiveHigh.

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 unsafeToActiveLow or unsafeToActiveHigh.

unsafeToActiveHigh :: 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.

unsafeToActiveLow :: 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.

unsafeFromActiveHigh Source #

Arguments

:: forall dom. KnownDomain dom 
=> Signal dom Bool

Reset signal that's True when active, and False when inactive.

-> 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.

unsafeFromActiveLow Source #

Arguments

:: forall dom. KnownDomain dom 
=> Signal dom Bool

Reset signal that's False when active, and True when inactive.

-> 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.

Deprecated

unsafeFromHighPolarity Source #

Arguments

:: forall dom. KnownDomain dom 
=> Signal dom Bool

Reset signal that's True when active, and False when inactive.

-> Reset dom 

Deprecated: Use unsafeFromActiveHigh instead. This function will be removed in Clash 1.12.

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 #

Arguments

:: forall dom. KnownDomain dom 
=> Signal dom Bool

Reset signal that's False when active, and True when inactive.

-> Reset dom 

Deprecated: Use unsafeFromActiveLow instead. This function will be removed in Clash 1.12.

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.

unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool Source #

Deprecated: Use unsafeToActiveHigh instead. This function will be removed in Clash 1.12.

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 #

Deprecated: Use unsafeToActiveLow instead. This function will be removed in Clash 1.12.

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.