Copyright | (C) 2013-2016 University of Twente 2017-2019 Myrtle Software Ltd 2017-2022 Google Inc. 2021-2023 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Extensions |
|
Synopsis
- data Signal (dom :: Domain) a = a :- (Signal dom a)
- head# :: Signal dom a -> a
- tail# :: Signal dom a -> Signal dom a
- type Domain = Symbol
- sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB)
- class (KnownSymbol dom, KnownNat (DomainPeriod dom)) => KnownDomain (dom :: Domain) where
- type KnownConf dom :: DomainConfiguration
- knownDomain :: SDomainConfiguration dom (KnownConf dom)
- type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf)
- knownDomainByName :: forall dom. KnownDomain dom => SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
- 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 :: {..} -> 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 family DomainConfigurationPeriod (config :: DomainConfiguration) :: Nat where ...
- type family DomainConfigurationActiveEdge (config :: DomainConfiguration) :: ActiveEdge where ...
- type family DomainConfigurationResetKind (config :: DomainConfiguration) :: ResetKind where ...
- type family DomainConfigurationInitBehavior (config :: DomainConfiguration) :: InitBehavior where ...
- type family DomainConfigurationResetPolarity (config :: DomainConfiguration) :: ResetPolarity where ...
- type HasSynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Synchronous)
- type HasAsynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous)
- type HasDefinedInitialValues (dom :: Domain) = (KnownDomain dom, DomainInitBehavior dom ~ 'Defined)
- 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]
- data Clock (dom :: Domain) = Clock {
- clockTag :: SSymbol dom
- clockPeriods :: Maybe (Signal dom Femtoseconds)
- newtype ClockN (dom :: Domain) = ClockN {}
- data DiffClock (dom :: Domain) = DiffClock ("p" ::: Clock dom) ("n" ::: ClockN dom)
- hzToPeriod :: (HasCallStack, Integral a) => Ratio Natural -> a
- periodToHz :: (HasCallStack, Fractional a) => Natural -> a
- data ClockAB
- clockTicks :: (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> [ClockAB]
- clockTicksEither :: Either Int64 (Signal domA Int64) -> Either Int64 (Signal domB Int64) -> [ClockAB]
- data Enable dom = Enable (Signal dom Bool)
- toEnable :: Signal dom Bool -> Enable dom
- fromEnable :: Enable dom -> Signal dom Bool
- enableGen :: Enable dom
- data Reset (dom :: Domain) = Reset (Signal dom Bool)
- unsafeToReset :: KnownDomain dom => Signal dom Bool -> Reset dom
- unsafeFromReset :: Reset dom -> Signal dom Bool
- unsafeToActiveHigh :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool
- unsafeToActiveLow :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool
- unsafeFromActiveHigh :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom
- unsafeFromActiveLow :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom
- invertReset :: KnownDomain dom => Reset dom -> Reset dom
- delay# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a
- register# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> a -> Signal dom a -> Signal dom a
- asyncRegister# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> a -> Signal dom a -> Signal dom a
- syncRegister# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> a -> Signal dom a -> Signal dom a
- registerPowerup# :: forall dom a. (KnownDomain dom, NFDataX a, HasCallStack) => Clock dom -> a -> a
- mux :: Applicative f => f Bool -> f a -> f a -> f a
- clockGen :: KnownDomain dom => Clock dom
- tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom
- newtype Femtoseconds = Femtoseconds Int64
- fsToHz :: (HasCallStack, Fractional a) => Femtoseconds -> a
- hzToFs :: HasCallStack => Ratio Natural -> Femtoseconds
- unFemtoseconds :: Femtoseconds -> Int64
- mapFemtoseconds :: (Int64 -> Int64) -> Femtoseconds -> Femtoseconds
- tbDynamicClockGen :: KnownDomain dom => Signal dom Femtoseconds -> Signal dom Bool -> Clock dom
- dynamicClockGen :: KnownDomain dom => Signal dom Femtoseconds -> Clock dom
- resetGen :: forall dom. KnownDomain dom => Reset dom
- resetGenN :: forall dom n. (KnownDomain dom, 1 <= n) => SNat n -> Reset dom
- (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool
- (.||.) :: Applicative f => f Bool -> f Bool -> f Bool
- simulate :: (NFDataX a, NFDataX b) => (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
- simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
- signalAutomaton :: forall dom a b. (Signal dom a -> Signal dom b) -> Automaton (->) a b
- sample :: (Foldable f, NFDataX a) => f a -> [a]
- sampleN :: (Foldable f, NFDataX a) => Int -> f a -> [a]
- fromList :: NFDataX a => [a] -> Signal dom a
- sample_lazy :: Foldable f => f a -> [a]
- sampleN_lazy :: Foldable f => Int -> f a -> [a]
- fromList_lazy :: [a] -> Signal dom a
- testFor :: Foldable f => Int -> f 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
- mapSignal# :: forall a b dom. (a -> b) -> Signal dom a -> Signal dom b
- signal# :: a -> Signal dom a
- appSignal# :: Signal dom (a -> b) -> Signal dom a -> Signal dom b
- foldr# :: (a -> b -> b) -> b -> Signal dom a -> b
- traverse# :: Applicative f => (a -> f b) -> Signal dom a -> f (Signal dom b)
- joinSignal# :: Signal dom (Signal dom a) -> Signal dom a
- unsafeFromHighPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom
- unsafeFromLowPolarity :: forall dom. KnownDomain dom => Signal dom Bool -> Reset dom
- unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool
- unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool
Datatypes
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
Lift a => Lift (Signal dom a :: Type) Source # | |
AssertionValue dom (Signal dom Bool) Source # | Stream of booleans, originating from a circuit |
Defined in Clash.Verification.Internal | |
Functor (Signal dom) Source # | |
Applicative (Signal dom) Source # | |
Defined in Clash.Signal.Internal | |
Foldable (Signal dom) Source # | NB: Not synthesizable NB: In "
|
Defined in Clash.Signal.Internal fold :: Monoid m => Signal dom m -> m # foldMap :: Monoid m => (a -> m) -> Signal dom a -> m # foldMap' :: Monoid m => (a -> m) -> Signal dom a -> m # foldr :: (a -> b -> b) -> b -> Signal dom a -> b # foldr' :: (a -> b -> b) -> b -> Signal dom a -> b # foldl :: (b -> a -> b) -> b -> Signal dom a -> b # foldl' :: (b -> a -> b) -> b -> Signal dom a -> b # foldr1 :: (a -> a -> a) -> Signal dom a -> a # foldl1 :: (a -> a -> a) -> Signal dom a -> a # toList :: Signal dom a -> [a] # null :: Signal dom a -> Bool # length :: Signal dom a -> Int # elem :: Eq a => a -> Signal dom a -> Bool # maximum :: Ord a => Signal dom a -> a # minimum :: Ord a => Signal dom a -> a # | |
Traversable (Signal dom) Source # | |
Defined in Clash.Signal.Internal | |
Fractional a => Fractional (Signal dom a) Source # | |
Num a => Num (Signal dom a) Source # | |
Defined in Clash.Signal.Internal (+) :: Signal dom a -> Signal dom a -> Signal dom a # (-) :: Signal dom a -> Signal dom a -> Signal dom a # (*) :: Signal dom a -> Signal dom a -> Signal dom a # negate :: Signal dom a -> Signal dom a # abs :: Signal dom a -> Signal dom a # signum :: Signal dom a -> Signal dom a # fromInteger :: Integer -> Signal dom a # | |
Show a => Show (Signal dom a) Source # | |
Arbitrary a => Arbitrary (Signal dom a) Source # | |
CoArbitrary a => CoArbitrary (Signal dom a) Source # | |
Defined in Clash.Signal.Internal coarbitrary :: Signal dom a -> Gen b -> Gen b # | |
Default a => Default (Signal dom a) Source # | |
Defined in Clash.Signal.Internal | |
NFDataX a => NFDataX (Signal domain a) Source # | |
Defined in Clash.Signal.Internal | |
Clocks (Clock c1, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # | |
type HasDomain dom1 (Signal dom2 a) Source # | |
Defined in Clash.Class.HasDomain.HasSpecificDomain | |
type TryDomain t (Signal dom a) Source # | |
Defined in Clash.Class.HasDomain.HasSingleDomain | |
type ClocksCxt (Clock c1, Signal pllLock Bool) Source # | |
Defined in Clash.Clocks | |
type NumOutClocks (Clock c1, Signal pllLock Bool) Source # | |
Defined in Clash.Clocks | |
type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) Source # | |
Defined in Clash.Clocks type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain pllLock) | |
type NumOutClocks (Clock c1, Clock c2, Signal pllLock Bool) Source # | |
Defined in Clash.Clocks | |
type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # | |
Defined in Clash.Clocks type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain pllLock) | |
type NumOutClocks (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # | |
Defined in Clash.Clocks |
Domains
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, KnownNat (DomainPeriod 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 {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = 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 #
knownDomainByName :: forall dom. KnownDomain dom => SSymbol dom -> SDomainConfiguration dom (KnownConf dom) Source #
Version of knownDomain
that takes a SSymbol
. For example:
>>>
knownDomainByName (SSymbol @"System")
SDomainConfiguration {sName = SSymbol @"System", sPeriod = SNat @10000, sActiveEdge = SRising, sResetKind = SAsynchronous, sInitBehavior = SDefined, sResetPolarity = SActiveHigh}
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 # | |
Binary 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 | |
|
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) => ...
type family DomainConfigurationPeriod (config :: DomainConfiguration) :: Nat where ... Source #
Helper type family for DomainPeriod
DomainConfigurationPeriod ('DomainConfiguration name period edge reset init polarity) = period |
type family DomainConfigurationActiveEdge (config :: DomainConfiguration) :: ActiveEdge where ... Source #
Helper type family for DomainActiveEdge
DomainConfigurationActiveEdge ('DomainConfiguration name period edge reset init polarity) = edge |
type family DomainConfigurationResetKind (config :: DomainConfiguration) :: ResetKind where ... Source #
Helper type family for DomainResetKind
DomainConfigurationResetKind ('DomainConfiguration name period edge reset init polarity) = reset |
type family DomainConfigurationInitBehavior (config :: DomainConfiguration) :: InitBehavior where ... Source #
Helper type family for DomainInitBehavior
DomainConfigurationInitBehavior ('DomainConfiguration name period edge reset init polarity) = init |
type family DomainConfigurationResetPolarity (config :: DomainConfiguration) :: ResetPolarity where ... Source #
Helper type family for DomainResetPolarity
DomainConfigurationResetPolarity ('DomainConfiguration name period edge reset init polarity) = polarity |
Convenience types
type HasSynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Synchronous) Source #
Convenience type to constrain a domain to have synchronous resets. Example usage:
myFunc :: HasSynchronousReset dom => ...
Using this type implies KnownDomain
.
type HasAsynchronousReset (dom :: Domain) = (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous) Source #
Convenience type to constrain a domain to have asynchronous resets. Example usage:
myFunc :: HasAsynchronousReset dom => ...
Using this type implies KnownDomain
.
type HasDefinedInitialValues (dom :: Domain) = (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) Source #
Convenience type to constrain a domain to have initial values. Example usage:
myFunc :: HasDefinedInitialValues dom => ...
Using this type implies KnownDomain
.
Note that there is no UnknownInitialValues dom
as a component that works
without initial values will also work if it does have them.
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"}
Clocks
data Clock (dom :: Domain) Source #
A clock signal belonging to a domain named dom.
Clock | |
|
Instances
data DiffClock (dom :: Domain) Source #
A differential clock signal belonging to a domain named dom. The clock
input of a design with such an input has two ports which are in antiphase.
The first input is the positive phase, the second the negative phase. When
using makeTopEntity
, the names of the inputs will end
in _p
and _n
respectively.
To create a differential clock in a test bench, you can use
clockToDiffClock
.
hzToPeriod :: (HasCallStack, Integral a) => Ratio Natural -> a 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
If the value hzToPeriod
is applied to is not of the type Ratio
Natural
, you can use hzToPeriod (
. Note that if realToFrac
f)f
is
negative, realToFrac
will give an
without a call stack, making debugging
cumbersome.Underflow
::
ArithException
Before Clash 1.8, this function always returned a Natural
. To get the old
behavior of this function, use a type application:
>>>
hzToPeriod @Natural 240e6
4166
- NB: This function is not synthesizable
- NB: This function is lossy. I.e.,
periodToHz . hzToPeriod /= id
.
periodToHz :: (HasCallStack, Fractional a) => Natural -> a Source #
Calculate the frequency 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
2.0e8
Note that if p
in periodToHz (
is negative,
fromIntegral
p)fromIntegral
will give an
without a call stack, making debugging
cumbersome.Underflow
::
ArithException
Before Clash 1.8, this function always returned a Ratio
Natural
. To get the old behavior of this function, use a type application:
>>>
periodToHz @(Ratio Natural) 5000
200000000 % 1
NB: This function is not synthesizable
Instances
Eq ClockAB Source # | |
Show ClockAB Source # | |
Generic ClockAB Source # | |
NFData ClockAB Source # | |
Defined in Clash.Signal.Internal | |
NFDataX ClockAB Source # | |
Defined in Clash.Signal.Internal | |
type Rep ClockAB Source # | |
Defined in Clash.Signal.Internal type Rep ClockAB = D1 ('MetaData "ClockAB" "Clash.Signal.Internal" "clash-prelude-1.8.1-inplace" 'False) (C1 ('MetaCons "ClockA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ClockB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClockAB" 'PrefixI 'False) (U1 :: Type -> Type))) |
clockTicks :: (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> [ClockAB] Source #
Given two clocks, produce a list of clock ticks indicating which clock
(or both) ticked. Can be used in components handling multiple clocks, such
as unsafeSynchronizer
or dual clock FIFOs.
If your primitive does not care about coincided clock edges, it should - by
convention - replace it by ClockB:ClockA:
.
clockTicksEither :: Either Int64 (Signal domA Int64) -> Either Int64 (Signal domB Int64) -> [ClockAB] Source #
Given two clock periods, produce a list of clock ticks indicating which clock
(or both) ticked. Can be used in components handling multiple clocks, such
as unsafeSynchronizer
or dual clock FIFOs.
If your primitive does not care about coincided clock edges, it should - by
convention - replace it by ClockB:ClockA:
.
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.
Resets
data Reset (dom :: Domain) Source #
A reset signal belonging to a domain called dom.
The underlying representation of resets is Bool
.
Instances
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.
:: 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.
:: 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.
invertReset :: KnownDomain dom => Reset dom -> Reset dom Source #
Invert reset signal
Basic circuits
delay# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a Source #
:: forall dom a. (KnownDomain dom, NFDataX a) | |
=> Clock dom | |
-> Reset dom | |
-> Enable dom | |
-> a | Power up value |
-> a | Reset value |
-> Signal dom a | |
-> Signal dom a |
A register with a power up and reset value. Power up values are not supported on all platforms, please consult the manual of your target platform and check the notes below.
Xilinx: power up values and reset values MUST be the same. If they are not, the Xilinx tooling will ignore the reset value and use the power up value instead. Source: MIA
Intel: power up values and reset values MUST be the same. If they are not, the Intel tooling will ignore the power up value and use the reset value instead. Source: https://www.intel.com/content/www/us/en/programmable/support/support-resources/knowledge-base/solutions/rd01072011_91.html
:: forall dom a. (KnownDomain dom, NFDataX a) | |
=> Clock dom | Clock signal |
-> Reset dom | Reset signal |
-> Enable dom | Enable signal |
-> a | Power up value |
-> a | Reset value |
-> Signal dom a | |
-> Signal dom a |
Version of register#
that simulates a register on an asynchronous
domain. Is synthesizable.
:: forall dom a. (KnownDomain dom, NFDataX a) | |
=> Clock dom | Clock signal |
-> Reset dom | Reset signal |
-> Enable dom | Enable signal |
-> a | Power up value |
-> a | Reset value |
-> Signal dom a | |
-> Signal dom a |
Version of register#
that simulates a register on a synchronous
domain. Not synthesizable.
registerPowerup# :: forall dom a. (KnownDomain dom, NFDataX a, HasCallStack) => Clock dom -> a -> a Source #
Acts like id
if given domain allows powerup values, but returns a
value constructed with deepErrorX
otherwise.
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.
tbClockGen :: KnownDomain testDom => Signal testDom Bool -> Clock testDom Source #
Clock generator to be used in the testBench function.
To be used like:
clkSystem en = tbClockGen @System en
Example
module Example where import Clash.Explicit.Prelude import Clash.Explicit.Testbench -- Fast domain: twice as fast as "Slow"createDomain
vSystem
{vName="Fast", vPeriod=10} -- Slow domain: twice as slow as "Fast"createDomain
vSystem
{vName="Slow", vPeriod=20} topEntity ::Clock
"Fast" ->Reset
"Fast" ->Enable
"Fast" ->Clock
"Slow" ->Signal
"Fast" (Unsigned 8) ->Signal
"Slow" (Unsigned 8, Unsigned 8) topEntity clk1 rst1 en1 clk2 i = let h = register clk1 rst1 en1 0 (register clk1 rst1 en1 0 i) l = register clk1 rst1 en1 0 i in unsafeSynchronizer clk1 clk2 (bundle (h, l)) testBench ::Signal
"Slow" Bool testBench = done where testInput =stimuliGenerator
clkA1 rstA1 $(listToVecTH
[1::Unsigned 8,2,3,4,5,6,7,8]) expectedOutput =outputVerifier
clkB2 rstB2 $(listToVecTH
[(0,0) :: (Unsigned 8, Unsigned 8),(1,2),(3,4),(5,6),(7,8)]) done = expectedOutput (topEntity clkA1 rstA1 enableGen clkB2 testInput) notDone = not <$> done clkA1 =tbClockGen
@"Fast" (unsafeSynchronizer clkB2 clkA1 notDone) clkB2 =tbClockGen
@"Slow" notDone rstA1 =resetGen
@"Fast" rstB2 =resetGen
@"Slow"
newtype Femtoseconds Source #
Femtoseconds expressed as an Int64
. Is a newtype to prevent accidental
mixups with picoseconds - the unit used in DomainConfiguration
.
Instances
fsToHz :: (HasCallStack, Fractional a) => Femtoseconds -> a Source #
Calculate the frequency in Hz, given the period in fs
I.e., to calculate the clock frequency of a clock with a period of 5000 fs:
>>>
fsToHz (Femtoseconds 5000)
2.0e11
NB: This function is not synthesizable
hzToFs :: HasCallStack => Ratio Natural -> Femtoseconds Source #
Calculate the period in fs, given a frequency in Hz
I.e., to calculate the clock period for a circuit to run at 240 MHz we get
>>>
hzToFs 240e6
Femtoseconds 4166666
If the value hzToFs
is applied to is not of the type Ratio
Natural
, you
can use hzToFs (
. Note that if realToFrac
f)f
is negative, realToFrac
will give an
without a call stack, making debugging
cumbersome.Underflow
::
ArithException
- NB: This function is not synthesizable
- NB: This function is lossy. I.e.,
fsToHz . hzToFs /= id
.
unFemtoseconds :: Femtoseconds -> Int64 Source #
Strip newtype wrapper Femtoseconds
mapFemtoseconds :: (Int64 -> Int64) -> Femtoseconds -> Femtoseconds Source #
Map Int64
fields in Femtoseconds
:: KnownDomain dom | |
=> Signal dom Femtoseconds | Clock period in femtoseconds.
|
-> Signal dom Bool | |
-> Clock dom |
Clock generator with dynamic clock periods for simulations. This is an
experimental feature and hence not part of the public API. Like tbClockGen
To be used like:
clkSystem = dynamicClockGen @System
See DomainConfiguration
for more information on how to use synthesis domains.
:: KnownDomain dom | |
=> Signal dom Femtoseconds | Clock period in femtoseconds.
|
-> Clock dom |
Clock generator with dynamic clock periods for simulations. This is an experimental feature and hence not part of the public API.
To be used like:
clkSystem = dynamicClockGen @System
See DomainConfiguration
for more information on how to use synthesis domains.
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.
:: 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.
Boolean connectives
Simulation functions (not synthesizable)
lazy version
simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] Source #
Automaton
List <-> Signal conversion (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
lazy versions
sample_lazy :: Foldable f => f a -> [a] Source #
sampleN_lazy :: Foldable f => Int -> f a -> [a] Source #
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
Type classes
Eq
-like
Ord
-like
Functor
mapSignal# :: forall a b dom. (a -> b) -> Signal dom a -> Signal dom b Source #
Applicative
Foldable
foldr# :: (a -> b -> b) -> b -> Signal dom a -> b Source #
NB: Not synthesizable
NB: In "
":foldr#
f z s
- The function
f
should be lazy in its second argument. - The
z
element will never be used.
Traversable
EXTREMELY EXPERIMENTAL
Deprecated
unsafeFromHighPolarity Source #
:: forall dom. KnownDomain dom | |
=> Signal dom Bool | Reset signal that's |
-> 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 #
:: forall dom. KnownDomain dom | |
=> Signal dom Bool | Reset signal that's |
-> 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.