Copyright | (C) 2013-2016 University of Twente 2016-2019 Myrtle Software 2017 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Extensions |
|
Clash has synchronous Signal
s in the form of:
Signal
(dom ::Symbol
) 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::Symbol
-- ^ Domain name , _period ::Nat
-- ^ Clock period in ps , _edge ::ActiveEdge
-- ^ Active edge of the clock , _reset ::ResetKind
-- ^ Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive) , _init ::InitBehavior
-- ^ Whether the initial (or "power up") value of memory elements is -- unknown/undefined, or configurable to a specific value , _polarity ::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 a standard implementation, called System
, that is
configured as follows:
instance KnownDomain System where type KnownConf System = 'DomainConfiguration System 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh knownDomain =SDomainConfiguration
SSymbol SNatSRising
SAsynchronous
SDefined
SActiveHigh
In words, "System" is a synthesis domain with a clock running with a period of 10000 ps (100 MHz). Memory elements update their state on the rising edge of the clock, can be reset asynchronously with regards to the clock, 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: 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!
Explicit clocks and resets, and meta-stability
When using multiple clocks and/or reset lines there are ways to accidentally introduce situations that are prone to metastability. These bugs are incredibly hard to debug as they often cannot be simulated, so it's best to prevent them in the first place. This section outlines the situations in which metastability arises and how to prevent it.
Two types of resets exist: synchronous and asynchronous resets. These reset types are encoded in a synthesis domain. For the following examples we assume the following exist:
DomainConfiguration
"SyncExample" _period _edgeSynchronous
_initDomainConfiguration
"AsyncExample" _period _edgeAsynchronous
_init
See the previous section on how to use domains.
We now go over the clock and reset line combinations and explain when they can potentially introduce situations prone to meta-stability:
Reset situation 1:
f ::
Reset
"SyncExample" ->Reset
"SyncExample" -> .. f x y = ..There are no problems here, because although x and y can have different values, components to these reset lines are reset synchronously, and there is no metastability situation.
Reset situation 2:
g ::
Reset
"AsyncExample" ->Reset
"AsyncExample" -> .. g x y = ..This situation can be prone to metastability, because although x and y belong to the same domain according to their domain, there is no guarantee that they actually originate from the same source. This means that one component can enter its reset state asynchronously to another component, inducing metastability in the other component.
Clock situation:
k ::
Clock
dom ->Clock
dom -> .. k x y = ..The situation above is potentially prone to metastability, because even though x and y belong to the same domain according to their domain, there is no guarantee that they actually originate from the same source. They could hence be connected to completely unrelated clock sources, and components can then induce metastable states in others.
Synopsis
- data Signal (dom :: Domain) a
- type Domain = Symbol
- 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
- newtype Enable dom = Enable (Signal dom Bool)
- toEnable :: Signal dom Bool -> Enable dom
- fromEnable :: Enable dom -> Signal dom Bool
- enableGen :: Enable dom
- data Clock (dom :: Domain)
- freqCalc :: Double -> Integer
- periodToHz :: Natural -> Double
- hzToPeriod :: HasCallStack => Double -> Natural
- unsafeSynchronizer :: forall dom1 dom2 a. (KnownDomain dom1, KnownDomain dom2) => Clock dom1 -> Clock dom2 -> Signal dom1 a -> Signal dom2 a
- veryUnsafeSynchronizer :: Int -> Int -> Signal dom1 a -> Signal dom2 a
- data Reset (dom :: Domain) = Reset (Signal dom Bool)
- 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
- convertReset :: forall domA domB. (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> Reset domA -> Reset domB
- resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Reset dom
- holdReset :: forall dom n. KnownDomain dom => Clock dom -> Enable dom -> SNat n -> Reset dom -> Reset dom
- enable :: Enable dom -> Signal dom Bool -> Enable dom
- dflipflop :: (KnownDomain dom, NFDataX a) => Clock dom -> Signal dom a -> Signal dom a
- delay :: (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a
- delayMaybe :: (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom (Maybe a) -> Signal dom a
- delayEn :: (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom Bool -> Signal dom a -> Signal dom a
- register :: (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom a
- regMaybe :: (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom (Maybe a) -> Signal dom a
- regEn :: (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom Bool -> Signal dom a -> Signal dom 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
- simulate :: (NFDataX a, NFDataX b) => (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
- simulateB :: (Bundle a, Bundle b, NFDataX a, NFDataX b) => (Unbundled dom1 a -> Unbundled dom2 b) -> [a] -> [b]
- simulateWithReset :: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b) -> [a] -> [b]
- simulateWithResetN :: (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) => SNat m -> a -> Int -> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b) -> [a] -> [b]
- simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
- simulateB_lazy :: (Bundle a, Bundle b) => (Unbundled dom1 a -> Unbundled dom2 b) -> [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
- fromListWithReset :: forall dom a. (KnownDomain dom, NFDataX a) => Reset dom -> 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
Synchronous signal
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!
See the module documentation of Clash.Signal for more information about domains.
Instances
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 # | |
Lift a => Lift (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 | |
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 # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source # | |
Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, 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 |
Domain
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
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 | |
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 ~ 'Asynchronous) => ...
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 in tact 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 in tact 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 in tact 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 | |
|
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
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
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.
Clock
data Clock (dom :: Domain) Source #
A clock signal belonging to a domain named dom.
Instances
freqCalc :: Double -> Integer Source #
Deprecated: Use hzToPeriod
instead.
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
>>>
freqCalc 240e6
4167
NB: This function is not synthesizable
periodToHz :: Natural -> Double 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
2.0e8
NB: This function is not synthesizable NB: This function is lossy. I.e., hzToPeriod . periodToHz /= id.
hzToPeriod :: HasCallStack => Double -> 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
4167
NB: This function is not synthesizable NB: This function is lossy. I.e., hzToPeriod . periodToHz /= id.
Synchronization primitive
:: forall dom1 dom2 a. (KnownDomain dom1, KnownDomain dom2) | |
=> Clock dom1 |
|
-> Clock dom2 |
|
-> Signal dom1 a | |
-> Signal dom2 a |
The unsafeSynchronizer
function is a primitive that must be used to
connect one clock domain to the other, and will be synthesized to a (bundle
of) wire(s) in the eventual circuit. This function should only be used as
part of a proper synchronization component, such as the following dual
flip-flop synchronizer:
dualFlipFlop :: Clock domA -> Clock domB -> Enable domA -> Enable domB -> Bit -> Signal domA Bit -> Signal domB Bit dualFlipFlop clkA clkB enA enB dflt =delay
clkB enB dflt .delay
clkB enB dflt .unsafeSynchronizer
clkA clkB
The unsafeSynchronizer
works in such a way that, given 2 clocks:
createDomain vSystem{vName="Dom7", vPeriod=7} clk7 ::Clock
Dom7 clk7 =clockGen
en7 ::Enable
Dom7 en7 =enableGen
and
createDomain vSystem{vName="Dom2", vPeriod=2} clk2 ::Clock
Dom2 clk2 =clockGen
en2 ::Enable
Dom2 en2 =enableGen
Oversampling followed by compression is the identity function plus 2 initial values:
delay
clkB enB dflt $unsafeSynchronizer
clkA clkB $delay
clkA enA dflt $unsafeSynchronizer
clkB clkA $delay
clkB enB s == dflt :- dflt :- s
Something we can easily observe:
oversampling clkA clkB enA enB dflt =delay
clkB enB dflt .unsafeSynchronizer
clkA clkB .delay
clkA enA dflt almostId clkA clkB enA enB dflt =delay
clkB enB dflt .unsafeSynchronizer
clkA clkB .delay
clkA enA dflt .unsafeSynchronizer
clkB clkA .delay
clkB enB dflt
>>>
sampleN 37 (oversampling clk7 clk2 en7 en2 0 (fromList [(1::Int)..10]))
[0,0,1,1,1,2,2,2,2,3,3,3,4,4,4,4,5,5,5,6,6,6,6,7,7,7,8,8,8,8,9,9,9,10,10,10,10]>>>
sampleN 12 (almostId clk2 clk7 en2 en7 0 (fromList [(1::Int)..10]))
[0,0,1,2,3,4,5,6,7,8,9,10]
veryUnsafeSynchronizer Source #
:: Int | Period of clock belonging to |
-> Int | Period of clock belonging to |
-> Signal dom1 a | |
-> Signal dom2 a |
Same as unsafeSynchronizer
, but with manually supplied clock periods.
Note: this unsafeSynchronizer is defined to be consistent with the vhdl and verilog
implementations however as only synchronous signals are represented in Clash this
cannot be done precisely and can lead to odd behaviour. For example,
sample $ unsafeSynchronizer
Dom2 Dom7 . unsafeSynchronizer
Dom7 Dom2 $ fromList [0..10]
> [0,4,4,4,7,7,7,7,11,11,11..
is quite different from the identity,
sample $ fromList [0..10]
> [0,1,2,3,4,5,6,7,8,9,10..
with values appearing from the "future".
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.
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 in case it needs to convert from an asynchronous to a synchronous reset.
resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Reset dom Source #
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
Example
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
where
key1R = isRising 1 key1
leds = mealy blinkerT (1, False, 0) key1R
:: 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]
Basic circuit functions
enable :: Enable dom -> Signal dom Bool -> Enable dom Source #
Merge enable signal with signal of bools
dflipflop :: (KnownDomain dom, NFDataX a) => Clock dom -> 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.
:: (KnownDomain dom, NFDataX a) | |
=> Clock dom | Clock |
-> Enable dom | Global enable |
-> a | Initial value |
-> Signal dom Bool | Enable |
-> Signal dom a | |
-> Signal dom a |
Version of delay
that only updates when its third 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 7 (delayEn systemClockGen enableGen 0 enable input)
[0,1,2,2,2,5,6]
:: (KnownDomain dom, NFDataX a) | |
=> Clock dom | Clock |
-> Reset dom | Reset, |
-> Enable dom | Global enable |
-> a | Reset value. If the domain has initial values enabled, the reset value will also be the initial value. |
-> Signal dom (Maybe a) | |
-> Signal dom a |
Version of register
that only updates its content when its fourth
argument is a Just
value. So given:
sometimes1 clk rst en = s where s =register
clk rst en Nothing (switch<$>
s) switch Nothing = Just 1 switch _ = Nothing countSometimes clk rst en = s where s =regMaybe
clk rst en 0 (plusM (pure
<$>
s) (sometimes1 clk rst en)) plusM = liftA2 (liftA2 (+))
We get:
>>>
sampleN 9 (sometimes1 systemClockGen resetGen enableGen)
[Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]>>>
sampleN 9 (count systemClockGen resetGen enableGen)
[0,0,0,1,1,2,2,3,3]
:: (KnownDomain dom, NFDataX a) | |
=> Clock dom | Clock |
-> Reset dom | Reset, |
-> Enable dom | Global enable |
-> a | Reset value. If the domain has initial values enabled, the reset value will also be the initial value. |
-> Signal dom Bool | Enable signal |
-> Signal dom a | |
-> Signal dom a |
Version of register
that only updates its content when its fourth
argument is asserted. So given:
oscillate clk rst en = let s = register
clk rst en False (not <$> s) in s
count clk rst en = let s = 'regEn clk rst en 0 (oscillate clk rst en) (s + 1) in s
We get:
>>>
sampleN 9 (oscillate systemClockGen resetGen enableGen)
[False,False,True,False,True,False,True,False,True]>>>
sampleN 9 (count systemClockGen resetGen enableGen)
[0,0,0,1,1,2,2,3,3]
Simulation and testbench functions
clockGen :: KnownDomain dom => Clock dom Source #
Clock generator for simulations. Do not use this clock generator for
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 #
Reset generator
To be used like:
rstSystem = resetGen @System
See tbClockGen
for example usage.
:: 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
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 (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 # | |
Bundle (Fixed rep int frac) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
Defined in Clash.Signal.Bundle bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
Defined in Clash.Signal.Bundle bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # | |
Defined in Clash.Signal.Bundle bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61, a62) Source # | |
Defined in Clash.Signal.Bundle type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61, a62) = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61, a62) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61, a62) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61, a62) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31, a32, a33, a34, a35, a36, a37, a38, a39, a40, a41, a42, a43, a44, a45, a46, a47, a48, a49, a50, a51, a52, a53, a54, a55, a56, a57, a58, a59, a60, a61, a62) Source # |
Simulation functions (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 |
-> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b) | Circuit to simulate |
-> [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 first value from
[a]
is fed to the circuit.
:: (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 cycle spent in reset) |
-> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b) | Circuit to simulate |
-> [a] | |
-> [b] |
Same as simulateWithReset
, but only sample the first Int output values.
lazy versions
simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] Source #
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
fromListWithReset :: forall dom a. (KnownDomain dom, NFDataX a) => Reset dom -> 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 = fromListWithReset @System rst Nothing [Just 'a', Just 'b', Just 'c']
>>>
sampleN 6 res
[Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
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