Copyright | (C) 2017 Google Inc. 2019 Myrtle Software Ltd 2022-2023 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Wires are fundamentally bidirectional, and in traditional HDLs we can exploit this aspect by explicitly marking the endpoint, or port, of such a wire as inout, thereby making this port function as both a source and a drain for the signals flowing over the wire.
Clash has support for inout
ports through the implementation of BiSignals.
To cleanly map to functions (and thus support software simulation using Haskell),
a BiSignal comes in two parts; the in part:
BiSignalIn
(ds ::BiSignalDefault
) (dom ::Domain
) (n :: Nat)
and the out part:
BiSignalOut
(ds ::BiSignalDefault
) (dom ::Domain
) (n :: Nat)
Where:
- The internal representation is a
BitVector
- n indicates the number of bits in the
BitVector
- dom is the clock- (and reset-) domain to which the memory elements manipulating these BiSignals belong.
- Lastly, ds indicates the default behavior for the BiSignal if nothing is being written (pull-down, pull-up, or undefined).
BiSignalIn
is used by Clash to generate the inout
ports on a HDL level,
while BiSignalOut
is only used for simulation purposes and generally discarded
by the compiler.
Example
The following describes a system where two circuits, in alternating fashion, read the current value from the bus, increment it, and write it on the next cycle.
import Clash.Explicit.Prelude import Clash.Signal.BiSignal -- | Alternatingly read / increment+write counter :: (Bool, Int) -- ^ Internal flip + previous read -> Int -- ^ Int from inout -> ((Bool, Int), Maybe Int) counter (write, prevread) i = ((write', prevread'), output) where output = if write then Just (succ prevread) else Nothing prevread' = if write then prevread else i write' = not write -- | Write on odd cyles f :: Clock System -> Reset System -> Enable System -> BiSignalIn 'Floating System (BitSize Int) -> BiSignalOut 'Floating System (BitSize Int) f clk rst en s = writeToBiSignal s (mealy clk rst en counter (False, 0) (readFromBiSignal s)) -- | Write on even cyles g :: Clock System -> Reset System -> Enable System -> BiSignalIn 'Floating System (BitSize Int) -> BiSignalOut 'Floating System (BitSize Int) g clk rst en s = writeToBiSignal s (mealy clk rst en counter (True, 0) (readFromBiSignal s)) -- | Connect the f and g circuits to the same bus topEntity :: Clock System -> Reset System -> Enable System -> Signal System Int topEntity clk rst en = readFromBiSignal bus' where bus = mergeBiSignalOuts $ f clk rst en bus' :> g clk rst en bus' :> Nil bus' = veryUnsafeToBiSignalIn bus
Synopsis
- data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)
- data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)
- data BiSignalDefault
- data SBiSignalDefault :: BiSignalDefault -> Type where
- class HasBiSignalDefault (ds :: BiSignalDefault) where
- pullUpMode :: BiSignalIn ds dom n -> SBiSignalDefault ds
- mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m
- readFromBiSignal :: (HasCallStack, BitPack a) => BiSignalIn ds d (BitSize a) -> Signal d a
- writeToBiSignal :: (HasCallStack, BitPack a, NFDataX a) => BiSignalIn ds d (BitSize a) -> Signal d (Maybe a) -> BiSignalOut ds d (BitSize a)
- veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n
Documentation
data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #
The in part of an inout port. BiSignalIn has the type role
>>>
:i BiSignalIn
type role BiSignalIn nominal nominal nominal ...
as it is not safe to coerce the default behaviour, synthesis domain or width of the data in the signal.
data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #
The out part of an inout port
Wraps (multiple) writing signals. The semantics are such that only one of the signals may write at a single time step.
BiSignalOut has the type role
>>>
:i BiSignalOut
type role BiSignalOut nominal nominal nominal ...
as it is not safe to coerce the default behaviour, synthesis domain or width of the data in the signal.
Instances
Semigroup (BiSignalOut defaultState dom n) Source # | NB: Not synthesizable |
Defined in Clash.Signal.BiSignal (<>) :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n # sconcat :: NonEmpty (BiSignalOut defaultState dom n) -> BiSignalOut defaultState dom n # stimes :: Integral b => b -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n # | |
Monoid (BiSignalOut defaultState dom n) Source # | Monoid instance to support concatenating NB: Not synthesizable |
Defined in Clash.Signal.BiSignal mempty :: BiSignalOut defaultState dom n # mappend :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n # mconcat :: [BiSignalOut defaultState dom n] -> BiSignalOut defaultState dom n # | |
type HasDomain dom1 (BiSignalOut ds dom2 n) Source # | |
Defined in Clash.Signal.BiSignal | |
type TryDomain t (BiSignalOut ds dom n) Source # | |
Defined in Clash.Signal.BiSignal |
data BiSignalDefault Source #
Used to specify the default behavior of a "BiSignal", i.e. what value is read when no value is being written to it.
PullUp | inout port behaves as if connected to a pull-up resistor |
PullDown | inout port behaves as if connected to a pull-down resistor |
Floating | inout port behaves as if is floating. Reading a floating "BiSignal" value in simulation will yield an errorX (undefined value). |
Instances
Show BiSignalDefault Source # | |
Defined in Clash.Signal.BiSignal showsPrec :: Int -> BiSignalDefault -> ShowS # show :: BiSignalDefault -> String # showList :: [BiSignalDefault] -> ShowS # |
data SBiSignalDefault :: BiSignalDefault -> Type where Source #
Singleton versions of BiSignalDefault
SPullUp :: SBiSignalDefault 'PullUp | |
SPullDown :: SBiSignalDefault 'PullDown | |
SFloating :: SBiSignalDefault 'Floating |
Instances
Given (SBiSignalDefault 'PullUp) Source # | |
Defined in Clash.Signal.BiSignal given :: SBiSignalDefault 'PullUp # | |
Given (SBiSignalDefault 'PullDown) Source # | |
Defined in Clash.Signal.BiSignal | |
Given (SBiSignalDefault 'Floating) Source # | |
Defined in Clash.Signal.BiSignal |
class HasBiSignalDefault (ds :: BiSignalDefault) where Source #
Type class for BiSignalDefault
:
can be used as a constraint and for obtaining the pull-up mode
pullUpMode :: BiSignalIn ds dom n -> SBiSignalDefault ds Source #
Instances
HasBiSignalDefault 'PullUp Source # | |
Defined in Clash.Signal.BiSignal pullUpMode :: forall (dom :: Domain) (n :: Nat). BiSignalIn 'PullUp dom n -> SBiSignalDefault 'PullUp Source # | |
HasBiSignalDefault 'PullDown Source # | |
Defined in Clash.Signal.BiSignal pullUpMode :: forall (dom :: Domain) (n :: Nat). BiSignalIn 'PullDown dom n -> SBiSignalDefault 'PullDown Source # | |
HasBiSignalDefault 'Floating Source # | |
Defined in Clash.Signal.BiSignal pullUpMode :: forall (dom :: Domain) (n :: Nat). BiSignalIn 'Floating dom n -> SBiSignalDefault 'Floating Source # |
mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m Source #
Combine several inout signals into one.
:: (HasCallStack, BitPack a) | |
=> BiSignalIn ds d (BitSize a) | A |
-> Signal d a |
Read the value from an inout port
:: (HasCallStack, BitPack a, NFDataX a) | |
=> BiSignalIn ds d (BitSize a) | |
-> Signal d (Maybe a) | Value to write
|
-> BiSignalOut ds d (BitSize a) |
Write to an inout port
veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n Source #
Converts the out
part of a BiSignal to an in
part. In simulation it
checks whether multiple components are writing and will error accordingly.
Make sure this is only called ONCE for every BiSignal.