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

Clash.Explicit.Reset

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

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

Expand
>>> 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]

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 . unsafeToHighPolarity
>>> 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) (unsafeFromHighPolarity 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.

data Reset (dom :: Domain) Source #

A reset signal belonging to a domain called dom.

The underlying representation of resets is Bool.

Instances

Instances details
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

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

Reset generator

To be used like:

rstSystem = resetGen @System

See tbClockGen for example usage.

resetGenN Source #

Arguments

:: 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]

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 the System clock domain.

NB: should only be used for simulation or the testBench function.

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 :: 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 #

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.

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