clash-prelude-0.5.0.1: CAES Language for Synchronous Hardware - Prelude library

Safe HaskellNone
LanguageHaskell2010

CLaSH.Signal.Explicit

Contents

Synopsis

Explicitly clocked synchronous signal

CλaSH supports explicitly clocked Signals in the form of: "CSignal clk a", where clk is a Natural number corresponding to the clock period of the clock the signal is synchronized to. NB: "Bad things"™ happen when you actually use a clock period of 0, so don't do that!

The clock periods 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 "CSignal 500 a" is synchronized to a clock that runs 6.5 times faster than the clock to which a "CSignal 3250 a" is synchronized to. NB: You should be judicious using a clock with period 1 as you can never create a clock that runs faster later on!

data CSignal clk a Source

A synchronized signal with samples of type a, explicitly synchronized to a clock with period clk

Instances

Functor (CSignal clk) 
Applicative (CSignal clk) 
Num a => Num (CSignal t a) 
Show a => Show (CSignal clk a) 
Default a => Default (CSignal clk a) 
Lift a => Lift (CSignal clk a) 

Clock domain crossing

newtype Clock clk Source

A clock with period clk

Constructors

Clock (SNat clk) 

veryUnsafeSynchronizer Source

Arguments

:: Clock clk1

Clock of the incoming signal

-> Clock clk2

Clock of the outgoing signal

-> CSignal clk1 a 
-> CSignal clk2 a 

Synchronisation function that is basically a represented by a (bundle of) wire(s) in hardware. This function should only be used as part of a proper synchronisation component, such as a dual flip-flop synchronizer, or a FIFO with an asynchronous memory element:

dualFlipFlop :: Clock clk1 -> Clock clk2
             -> CSignal clk1 Bit -> CSignal clk2 Bit
dualFlipFlop clk1 clk2 = cregister clk2 L . cregister clk2 L . veryUnsafeSynchronizer clk1 clk2

The veryUnsafeSynchronizer works in such a way that, given 2 clocks:

clk7 = Clock d7
clk2 = Clock d2

Oversampling followed by compression is the identity function plus 2 initial values:

cregister clk7 i $
veryUnsafeSynchronizer clk2 clk7 $
cregister clk2 j $
veryUnsafeSynchronizer clk7 clk2 $
cregister clk7 k s

==

i :- j :- s

Something we can easily observe:

oversampling = cregister clk2 99 . veryUnsafeSynchronizer clk7 clk2 . cregister clk7 50
almostId     = cregister clk7 70 . veryUnsafeSynchronizer clk2 clk7
             . cregister clk2 99 . veryUnsafeSynchronizer clk7 clk2 . cregister clk7 50
>>> csample (oversampling (cfromList [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, ...
>>> csample (almostId (cfromList [1..10]))
[70, 99,1,2,3,4,5,6,7,8,9,10,...

fromImplicit :: Signal a -> CSignal 1000 a Source

Implicitly clocked signals have a clock with period 1000

fromExplicit :: CSignal 1000 a -> Signal a Source

Implicitly clocked signals have a clock with period 1000

Basic circuit functions

csignal :: a -> CSignal t a Source

Create a constant CSignal from a combinational value

>>> csample (csignal 4)
[4, 4, 4, 4, ...

cregister :: Clock clk -> a -> CSignal clk a -> CSignal clk a Source

cregister i s delays the values in CSignal s for one cycle, and sets the value at time 0 to i

clk100 = Clock d100
>>> csampleN 3 (cregister d100 8 (fromList [1,2,3,4]))
[8,1,2]

class CPack a where Source

Isomorphism between a CSignal clk of a product type (e.g. a tuple) and a product type of CSignal clk's

Instances of CPack must satisfy the following laws:

cpack clk . cunpack clk = id
cunpack clk . cpack clk = id

Associated Types

type CSignalP clk a Source

Methods

cpack :: Clock clk -> CSignalP clk a -> CSignal clk a Source

Example:

cpack :: Clock clk -> (CSignal clk a, CSignal clk b) -> CSignal clk (a,b)

However:

cpack :: Clock clk -> CSignal clk Bit -> CSignal clk Bit

cunpack :: Clock clk -> CSignal clk a -> CSignalP clk a Source

Example:

cunpack :: Clock clk -> CSignal clk (a,b) -> (CSignal clk a, CSignal clk b)

However:

cunpack :: Clock clk -> CSignal clk Bit -> CSignal clk Bit

Instances

CPack Bool 
CPack Double 
CPack Float 
CPack Int 
CPack Integer 
CPack () 
CPack Bit 
CPack (Signed n) 
CPack (Unsigned n) 
CPack (a, b) 
CPack (Vec n a) 
CPack (a, b, c) 
CPack (Fixed frac rep size) 
CPack (a, b, c, d) 
CPack (a, b, c, d, e) 
CPack (a, b, c, d, e, f) 
CPack (a, b, c, d, e, f, g) 
CPack (a, b, c, d, e, f, g, h) 

Simulation functions

csimulate :: (CSignal clk1 a -> CSignal clk2 b) -> [a] -> [b] Source

Simulate a (CSignal clk1 a -> Signal clk2 b) function given a list of samples of type a

>>> simulate (register 8) [1, 2, 3, ...
[8, 1, 2, 3, ...

csimulateP Source

Arguments

:: (CPack a, CPack b) 
=> Clock clk1

Clock of the incoming signal

-> Clock clk2

Clock of the outgoing signal

-> (CSignalP clk1 a -> CSignalP clk2 b)

Function to simulate

-> [a] 
-> [b] 

Simulate a (CSignalP clk1 a -> CSignalP clk2 b) function given a list of samples of type a

clk100 = Clock d100
>>> csimulateP clk100 clk100 (cunpack clk100 . cregister clk100 (8,8) . cpack clk100) [(1,1), (2,2), (3,3), ...
[(8,8), (1,1), (2,2), (3,3), ...

List <-> CSignal conversion

csample :: CSignal t a -> [a] Source

Get an infinite list of samples from a CSignal

The elements in the list correspond to the values of the CSignal at consecutive clock cycles

csample s == [s0, s1, s2, s3, ...

csampleN :: Int -> CSignal t a -> [a] Source

Get a list of n samples from a CSignal

The elements in the list correspond to the values of the CSignal at consecutive clock cycles

csampleN 3 s == [s0, s1, s2]

cfromList :: [a] -> CSignal t a Source

Create a CSignal from a list

Every element in the list will correspond to a value of the signal for one clock cycle.

NB: Simulation only!

>>> csampleN 2 (cfromList [1,2,3,4,5])
[1,2]