| Copyright | (C) 2013-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. |
|---|---|
| License | BSD2 (see the file LICENSE) |
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
| Safe Haskell | Unsafe |
| Language | Haskell2010 |
| Extensions |
|
Clash.Signal.Internal
Contents
Description
Synopsis
- data Domain = Dom {
- domainName :: Symbol
- clkPeriod :: Nat
- data Signal (domain :: Domain) a = a :- (Signal domain a)
- data Clock (domain :: Domain) (gated :: ClockKind) where
- data ClockKind
- clockPeriod :: Num a => Clock domain gated -> a
- clockEnable :: Clock domain gated -> Maybe (Signal domain Bool)
- clockGate :: Clock domain gated -> Signal domain Bool -> Clock domain Gated
- data Reset (domain :: Domain) (synchronous :: ResetKind) where
- Sync :: Signal domain Bool -> Reset domain Synchronous
- Async :: Signal domain Bool -> Reset domain Asynchronous
- data ResetKind
- unsafeFromAsyncReset :: Reset domain Asynchronous -> Signal domain Bool
- unsafeToAsyncReset :: Signal domain Bool -> Reset domain Asynchronous
- fromSyncReset :: Reset domain Synchronous -> Signal domain Bool
- unsafeToSyncReset :: Signal domain Bool -> Reset domain Synchronous
- delay# :: HasCallStack => Clock domain gated -> Signal domain a -> Signal domain a
- register# :: HasCallStack => Clock domain gated -> Reset domain synchronous -> a -> Signal domain a -> Signal domain a
- mux :: Applicative f => f Bool -> f a -> f a -> f a
- clockGen :: (domain ~ Dom nm period, KnownSymbol nm, KnownNat period) => Clock domain Source
- tbClockGen :: (domain ~ Dom nm period, KnownSymbol nm, KnownNat period) => Signal domain Bool -> Clock domain Source
- asyncResetGen :: Reset domain Asynchronous
- syncResetGen :: (domain ~ Dom n clkPeriod, KnownNat clkPeriod) => Reset domain Synchronous
- (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool
- (.||.) :: Applicative f => f Bool -> f Bool -> f Bool
- simulate :: (NFData a, NFData b) => (Signal domain1 a -> Signal domain2 b) -> [a] -> [b]
- simulate_lazy :: (Signal domain1 a -> Signal domain2 b) -> [a] -> [b]
- sample :: (Foldable f, NFData a) => f a -> [a]
- sampleN :: (Foldable f, NFData a) => Int -> f a -> [a]
- fromList :: NFData a => [a] -> Signal domain a
- sample_lazy :: Foldable f => f a -> [a]
- sampleN_lazy :: Foldable f => Int -> f a -> [a]
- fromList_lazy :: [a] -> Signal domain a
- testFor :: Foldable f => Int -> f Bool -> Property
- (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
- (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
- (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- mapSignal# :: (a -> b) -> Signal domain a -> Signal domain b
- signal# :: a -> Signal domain a
- appSignal# :: Signal domain (a -> b) -> Signal domain a -> Signal domain b
- foldr# :: (a -> b -> b) -> b -> Signal domain a -> b
- traverse# :: Applicative f => (a -> f b) -> Signal domain a -> f (Signal domain b)
- joinSignal# :: Signal domain (Signal domain a) -> Signal domain a
Datatypes
A domain with a name (Symbol) and a clock period (Nat) in ps
Constructors
| Dom | |
Fields
| |
data Signal (domain :: Domain) a Source #
CλaSH has synchronous Signals in the form of:
Signal(domain ::Domain) a
Where a is the type of the value of the Signal, for example Int or Bool,
and domain is the clock- (and reset-) domain to which the memory elements
manipulating these Signals belong.
The type-parameter, domain, is of the kind Domain which has types of the
following shape:
data Domain = Dom { domainName :: Symbol, clkPeriod :: Nat }
Where domainName is a type-level string (Symbol) representing
the name of the clock- (and reset-) domain, and clkPeriod is a type-level
natural number (Nat) representing the clock period (in ps)
of the clock lines in the clock-domain.
- 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
1as you can never create a clock that goes any faster!
Instances
| Functor (Signal domain) Source # | |
| Applicative (Signal domain) Source # | |
Methods pure :: a -> Signal domain a # (<*>) :: Signal domain (a -> b) -> Signal domain a -> Signal domain b # liftA2 :: (a -> b -> c) -> Signal domain a -> Signal domain b -> Signal domain c # (*>) :: Signal domain a -> Signal domain b -> Signal domain b # (<*) :: Signal domain a -> Signal domain b -> Signal domain a # | |
| Foldable (Signal domain) Source # | NB: Not synthesisable NB: In "
|
Methods fold :: Monoid m => Signal domain m -> m # foldMap :: Monoid m => (a -> m) -> Signal domain a -> m # foldr :: (a -> b -> b) -> b -> Signal domain a -> b # foldr' :: (a -> b -> b) -> b -> Signal domain a -> b # foldl :: (b -> a -> b) -> b -> Signal domain a -> b # foldl' :: (b -> a -> b) -> b -> Signal domain a -> b # foldr1 :: (a -> a -> a) -> Signal domain a -> a # foldl1 :: (a -> a -> a) -> Signal domain a -> a # toList :: Signal domain a -> [a] # null :: Signal domain a -> Bool # length :: Signal domain a -> Int # elem :: Eq a => a -> Signal domain a -> Bool # maximum :: Ord a => Signal domain a -> a # minimum :: Ord a => Signal domain a -> a # | |
| Traversable (Signal domain) Source # | |
Methods traverse :: Applicative f => (a -> f b) -> Signal domain a -> f (Signal domain b) # sequenceA :: Applicative f => Signal domain (f a) -> f (Signal domain a) # mapM :: Monad m => (a -> m b) -> Signal domain a -> m (Signal domain b) # sequence :: Monad m => Signal domain (m a) -> m (Signal domain a) # | |
| Fractional a => Fractional (Signal domain a) Source # | |
| Num a => Num (Signal domain a) Source # | |
Methods (+) :: Signal domain a -> Signal domain a -> Signal domain a # (-) :: Signal domain a -> Signal domain a -> Signal domain a # (*) :: Signal domain a -> Signal domain a -> Signal domain a # negate :: Signal domain a -> Signal domain a # abs :: Signal domain a -> Signal domain a # signum :: Signal domain a -> Signal domain a # fromInteger :: Integer -> Signal domain a # | |
| Show a => Show (Signal domain a) Source # | |
| Lift a => Lift (Signal domain a) Source # | |
| Default a => Default (Signal domain a) Source # | |
| Arbitrary a => Arbitrary (Signal domain a) Source # | |
| CoArbitrary a => CoArbitrary (Signal domain a) Source # | |
Methods coarbitrary :: Signal domain a -> Gen b -> Gen b | |
Clocks
data Clock (domain :: Domain) (gated :: ClockKind) where Source #
A clock signal belonging to a domain
Distinction between gated and ungated clocks
Constructors
| Source | A clock signal coming straight from the clock source |
| Gated | A clock signal that has been gated |
Instances
| Eq ClockKind Source # | |
| Ord ClockKind Source # | |
| Show ClockKind Source # | |
| Generic ClockKind Source # | |
| NFData ClockKind Source # | |
| type Rep ClockKind Source # | |
clockPeriod :: Num a => Clock domain gated -> a Source #
Clock gating
clockGate :: Clock domain gated -> Signal domain Bool -> Clock domain Gated Source #
Clock gating primitive
Resets
data Reset (domain :: Domain) (synchronous :: ResetKind) where Source #
A reset signal belonging to a domain.
The underlying representation of resets is Bool. Note that all components
in the clash-prelude package have an active-high reset port, i.e., the
component is reset when the reset port is True.
Constructors
| Sync :: Signal domain Bool -> Reset domain Synchronous | |
| Async :: Signal domain Bool -> Reset domain Asynchronous |
The "kind" of reset
Given a situation where a reset is asserted, and then de-asserted at the active flank of the clock, we can observe the difference between a synchronous reset and an asynchronous reset:
Synchronous reset
registerS :: Clock domain gated -> Reset domain Synchronous -> Signal domain Int -> Signal domain Int registerS = register
>>>printX (sampleN 4 (registerS (clockGen @System) (syncResetGen @System) 0 (fromList [1,2,3])))[X,0,2,3]
Asynchronous reset
registerA :: Clock domain gated -> Reset domain Asynchronous -> Signal domain Int -> Signal domain Int registerA = register
>>>sampleN 4 (registerA (clockGen @System) (asyncResetGen @System) 0 (fromList [1,2,3]))[0,1,2,3]
Constructors
| Synchronous | Components with a synchronous reset port produce the reset value when:
|
| Asynchronous | Components with an asynchronous reset port produce the reset value when:
|
Instances
| Eq ResetKind Source # | |
| Ord ResetKind Source # | |
| Show ResetKind Source # | |
| Generic ResetKind Source # | |
| NFData ResetKind Source # | |
| type Rep ResetKind Source # | |
unsafeFromAsyncReset :: Reset domain Asynchronous -> Signal domain Bool Source #
unsafeFromAsyncReset is unsafe because it can introduce:
unsafeToAsyncReset :: Signal domain Bool -> Reset domain Asynchronous Source #
unsafeToAsyncReset is unsafe because it can introduce:
- combinational loops
Example
resetSynchronizer
:: Clock domain gated
-> Reset domain 'Asynchronous
-> Reset domain 'Asynchronous
resetSynchronizer clk rst =
let r1 = register clk rst True (pure False)
r2 = register clk rst True r1
in unsafeToAsyncReset r2
fromSyncReset :: Reset domain Synchronous -> Signal domain Bool Source #
It is safe to treat synchronous resets as Bool signals
unsafeToSyncReset :: Signal domain Bool -> Reset domain Synchronous Source #
unsafeToSyncReset is unsafe because:
- It can lead to meta-stability issues in the presence of asynchronous resets.
Basic circuits
register# :: HasCallStack => Clock domain gated -> Reset domain synchronous -> a -> Signal domain a -> Signal domain a Source #
mux :: Applicative f => f Bool -> f a -> f a -> f a Source #
Simulation and testbench functions
clockGen :: (domain ~ Dom nm period, KnownSymbol nm, KnownNat period) => Clock domain Source Source #
Clock generator for simulations. Do not use this clock generator for
for the testBench function, use tbClockGen instead.
To be used like:
type DomA = Dom "A" 1000 clkA = clockGen @DomA
tbClockGen :: (domain ~ Dom nm period, KnownSymbol nm, KnownNat period) => Signal domain Bool -> Clock domain Source Source #
Clock generator to be used in the testBench function.
To be used like:
type DomA = Dom "A" 1000 clkA en = clockGen @DomA en
Example
type DomA1 = Dom "A" 1 -- fast, twice as fast as slow
type DomB2 = Dom "B" 2 -- slow
topEntity
:: Clock DomA1 Source
-> Reset DomA1 Asynchronous
-> Clock DomB2 Source
-> Signal DomA1 (Unsigned 8)
-> Signal DomB2 (Unsigned 8, Unsigned 8)
topEntity clk1 rst1 clk2 i =
let h = register clk1 rst1 0 (register clk1 rst1 0 i)
l = register clk1 rst1 0 i
in unsafeSynchronizer clk1 clk2 (bundle (h,l))
testBench
:: Signal DomB2 Bool
testBench = done
where
testInput = stimuliGenerator clkA1 rstA1 $(listToVecTH [1::Unsigned 8,2,3,4,5,6,7,8])
expectedOutput = outputVerifier clkB2 rstB2 $(listToVecTH [(0,0) :: (Unsigned 8, Unsigned 8),(1,2),(3,4),(5,6),(7,8)])
done = expectedOutput (topEntity clkA1 rstA1 clkB2 testInput)
done' = not <$> done
clkA1 = tbClockGen @DomA1 (unsafeSynchronizer clkB2 clkA1 done')
clkB2 = tbClockGen @DomB2 done'
rstA1 = asyncResetGen @DomA1
rstB2 = asyncResetGen @DomB2
asyncResetGen :: Reset domain Asynchronous Source #
Asynchronous reset generator, for simulations and the testBench function.
To be used like:
type DomA = Dom "A" 1000 rstA = asyncResetGen @DomA
NB: Can only be used for components with an active-high reset port, which all clash-prelude components are.
Example
type Dom2 = Dom "dom" 2
type Dom7 = Dom "dom" 7
type Dom9 = Dom "dom" 9
topEntity
:: Clock Dom2 Source
-> Clock Dom7 Source
-> Clock Dom9 Source
-> Signal Dom7 Integer
-> Signal Dom9 Integer
topEntity clk2 clk7 clk9 i = delay clk9 (unsafeSynchronizer clk2 clk9 (delay clk2 (unsafeSynchronizer clk7 clk2 (delay clk7 i))))
{--}
testBench
:: Signal Dom9 Bool
testBench = done
where
testInput = stimuliGenerator clk7 rst7 $(listToVecTH [(1::Integer)..10])
expectedOutput = outputVerifier clk9 rst9
((undefined :> undefined :> Nil) ++ $(listToVecTH ([2,3,4,5,7,8,9,10]::[Integer])))
done = expectedOutput (topEntity clk2 clk7 clk9 testInput)
done' = not <$> done
clk2 = tbClockGen @Dom2 (unsafeSynchronizer clk9 clk2 done')
clk7 = tbClockGen @Dom7 (unsafeSynchronizer clk9 clk7 done')
clk9 = tbClockGen @Dom9 done'
rst7 = asyncResetGen @Dom7
rst9 = asyncResetGen @Dom9
syncResetGen :: (domain ~ Dom n clkPeriod, KnownNat clkPeriod) => Reset domain Synchronous Source #
Synchronous reset generator, for simulations and the testBench function.
To be used like:
type DomA = Dom "A" 1000 rstA = syncResetGen @DomA
NB: Can only be used for components with an active-high reset port, which all clash-prelude components are.
Boolean connectives
Simulation functions (not synthesisable)
lazy version
simulate_lazy :: (Signal domain1 a -> Signal domain2 b) -> [a] -> [b] Source #
List <-> Signal conversion (not synthesisable)
fromList :: NFData a => [a] -> Signal domain 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 synthesisable
lazy versions
sample_lazy :: Foldable f => f a -> [a] Source #
sampleN_lazy :: Foldable f => Int -> f a -> [a] Source #
fromList_lazy :: [a] -> Signal domain 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 synthesisable
QuickCheck combinators
Type classes
Eq-like
Ord-like
Functor
mapSignal# :: (a -> b) -> Signal domain a -> Signal domain b Source #
Applicative
Foldable
foldr# :: (a -> b -> b) -> b -> Signal domain a -> b Source #
NB: Not synthesisable
NB: In "":foldr# f z s
- The function
fshould be lazy in its second argument. - The
zelement will never be used.