Copyright | (C) 2013-2015, University of Twente |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Extensions |
|
- data Signal' clk a
- data Clock = Clk Symbol Nat
- data SClock clk where
- sclock :: (KnownSymbol name, KnownNat period) => SClock (Clk name period)
- withSClock :: (KnownSymbol name, KnownNat period) => (SClock (Clk name period) -> a) -> a
- type SystemClock = Clk "system" 1000
- systemClock :: SClock SystemClock
- unsafeSynchronizer :: SClock clk1 -> SClock clk2 -> Signal' clk1 a -> Signal' clk2 a
- register' :: SClock clk -> a -> Signal' clk a -> Signal' clk a
- regEn' :: SClock clk -> a -> Signal' clk Bool -> Signal' clk a -> Signal' clk a
- class Bundle a where
- type Unbundled' clk a
- bundle' :: SClock clk -> Unbundled' clk a -> Signal' clk a
- unbundle' :: SClock clk -> Signal' clk a -> Unbundled' clk a
- simulateB' :: (Bundle a, Bundle b) => SClock clk1 -> SClock clk2 -> (Unbundled' clk1 a -> Unbundled' clk2 b) -> [a] -> [b]
Explicitly clocked synchronous signal
CλaSH supports explicitly clocked Signal
s in the form of:
Signal'
(clk ::Clock
) a
Where a
is the type of the elements, and clk
is the clock to which the
signal is synchronised. The type-parameter, clk
, is of the kind Clock
which
has types of the following shape:
Clk {- name :: -}Symbol
{- period :: -}Nat
Where name
is a type-level string (Symbol
) representing the the
name of the clock, and period
is a type-level natural number (Nat
)
representing the clock period. Two concrete instances of a Clk
could be:
type ClkA500 = Clk "A500" 500 type ClkB3250 = Clk "B3250" 3250
The periods of these clocks are however dimension-less, they do not refer to any explicit time-scale (e.g. nano-seconds). The reason for the lack of an explicit time-scale is that the CλaSH compiler would not be able guarantee that the circuit can run at the specified frequency. The clock periods are just there to indicate relative frequency differences between two different clocks. That is, a signal:
Signal'
ClkA500 a
is synchronized to a clock that runs 6.5 times faster than the clock to which the signal:
Signal'
ClkB3250 a
is synchronized to.
- 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 faster!
A synchronized signal with samples of type a
, explicitly synchronized to
a clock clk
NB: The constructor, (
, is not synthesisable.:-
)
Functor (Signal' clk) Source | |
Applicative (Signal' clk) Source | |
Foldable (Signal' clk) Source | NB: Not synthesisable NB: In "
|
Traversable (Signal' clk) Source | |
Bounded a => Bounded (Signal' clk a) Source | |
Enum a => Enum (Signal' clk a) Source | |
Eq (Signal' clk a) Source | WARNING: ( |
Fractional a => Fractional (Signal' clk a) Source | |
Integral a => Integral (Signal' clk a) Source | WARNING: |
Num a => Num (Signal' clk a) Source | |
Ord a => Ord (Signal' clk a) Source | WARNING: |
(Num a, Ord a) => Real (Signal' clk a) Source | WARNING: |
Show a => Show (Signal' clk a) Source | |
Arbitrary a => Arbitrary (Signal' clk a) Source | |
CoArbitrary a => CoArbitrary (Signal' clk a) Source | |
Bits a => Bits (Signal' clk a) Source | WARNING: |
FiniteBits a => FiniteBits (Signal' clk a) Source | |
Default a => Default (Signal' clk a) Source | |
Lift a => Lift (Signal' clk a) Source | |
SaturatingNum a => SaturatingNum (Signal' clk a) Source | |
ExtendingNum a b => ExtendingNum (Signal' clk a) (Signal' clk b) Source | |
type AResult (Signal' clk a) (Signal' clk b) = Signal' clk (AResult a b) Source | |
type MResult (Signal' clk a) (Signal' clk b) = Signal' clk (MResult a b) Source |
Clock domain crossing
Clock
Singleton value for a type-level Clock
with the given name
and period
withSClock :: (KnownSymbol name, KnownNat period) => (SClock (Clk name period) -> a) -> a Source
Supply a function with a singleton clock clk
according to the context
type SystemClock = Clk "system" 1000 Source
The standard system clock with a period of 1000
systemClock :: SClock SystemClock Source
The singleton clock for SystemClock
Synchronisation primitive
:: SClock clk1 |
|
-> SClock clk2 |
|
-> Signal' clk1 a | |
-> Signal' clk2 a |
The unsafeSynchronizer
function is a primitive that must be used to
connect one clock domain to the other, and will be synthesised to a (bundle
of) wire(s) in the eventual circuit. This function should only be used as
part of a proper synchronisation component, such as the following dual
flip-flop synchronizer:
dualFlipFlop :: SClock clkA -> SClock clkB -> Signal' clkA Bit -> Signal' clkB Bit dualFlipFlop clkA clkB =register'
clkB low .register'
clkB low .unsafeSynchronizer
clkA clkB
The unsafeSynchronizer
works in such a way that, given 2 clocks:
type Clk7 =Clk
"clk7" 7 clk7 ::SClock
Clk7 clk7 =sclock
and
type Clk2 =Clk
"clk2" 2 clk2 ::SClock
Clk2 clk2 =sclock
Oversampling followed by compression is the identity function plus 2 initial values:
register'
clk7 i $unsafeSynchronizer
clk2 clk7 $register'
clk2 j $unsafeSynchronizer
clk7 clk2 $register'
clk7 k s == i :- j :- s
Something we can easily observe:
oversampling =register'
clk2 99 .unsafeSynchronizer
clk7 clk2 .register'
clk7 50 almostId =register'
clk7 70 .unsafeSynchronizer
clk2 clk7 .register'
clk2 99 .unsafeSynchronizer
clk7 clk2 .register'
clk7 50
>>>
sampleN 37 (oversampling (fromList [1..10]))
[99,50,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 (fromList [1..10]))
[70,99,1,2,3,4,5,6,7,8,9,10]
Basic circuit functions
regEn' :: SClock clk -> a -> Signal' clk Bool -> Signal' clk a -> Signal' clk a Source
Version of register'
that only updates its content when its second
argument is asserted. So given:
type ClkA =Clk
"A" 100 clkA ::SClock
ClkA clkA =sclock
oscillate =register'
clkA False (not1
oscillate) count =regEn'
clkA 0 oscillate (count + 1)
We get:
>>>
sampleN 8 oscillate
[False,True,False,True,False,True,False,True]>>>
sampleN 8 count
[0,0,1,1,2,2,3,3]
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 instanceBundle
D where typeUnbundled'
clk D =Signal'
clk Dbundle'
_ s = sunbundle'
_ s = s
Nothing
type Unbundled' clk a Source
bundle' :: SClock clk -> Unbundled' clk a -> Signal' clk a Source
Example:
bundle' :: (Signal'
clk a,Signal'
clk b) ->Signal'
clk (a,b)
However:
bundle' ::Signal'
clkBit
->Signal'
clkBit
unbundle' :: SClock clk -> Signal' clk a -> Unbundled' clk a Source
Bundle Bool Source | |
Bundle Double Source | |
Bundle Float Source | |
Bundle Int Source | |
Bundle Integer Source | |
Bundle () Source | |
Bundle (Maybe a) Source | |
Bundle (Index n) Source | |
Bundle (BitVector n) Source | |
Bundle (Signed n) Source | |
Bundle (Unsigned n) Source | |
Bundle (Either a b) Source | |
Bundle (a, b) Source | |
KnownNat n => Bundle (Vec n a) Source | |
Bundle (a, b, c) Source | |
Bundle (Fixed rep int frac) Source | |
Bundle (a, b, c, d) Source | |
Bundle (a, b, c, d, e) Source | |
Bundle (a, b, c, d, e, f) Source | |
Bundle (a, b, c, d, e, f, g) Source | |
Bundle (a, b, c, d, e, f, g, h) Source |
Simulation functions (not synthesisable)
:: (Bundle a, Bundle b) | |
=> SClock clk1 |
|
-> SClock clk2 |
|
-> (Unbundled' clk1 a -> Unbundled' clk2 b) | Function to simulate |
-> [a] | |
-> [b] |
Simulate a (
) function given a
list of samples of type Unbundled'
clk1 a -> Unbundled'
clk2 ba
>>>
simulateB' clkA clkA (unbundle' clkA . register' clkA (8,8) . bundle' clkA) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)...
NB: This function is not synthesisable