clash-prelude-0.6.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 :: 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:

CSignal ClkA500 a

is synchronized to a clock that runs 6.5 times faster than the clock to which the signal:

CSignal 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!

data CSignal clk a Source

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

NB: The constructor, (:-), is not synthesisable.

Instances

Functor (CSignal clk) 
Applicative (CSignal clk) 
Foldable (CSignal clk)

NB: Not synthesisable

NB: In "foldr f z s":

  • The function f should be lazy in its second argument.
  • The z element will never be used.
Traversable (CSignal clk) 
Bounded a => Bounded (CSignal clk a) 
Enum a => Enum (CSignal clk a)

WARNING: fromEnum is undefined, use fromEnum1 instead

Eq (CSignal clk a)

WARNING: (==) and (/=) are undefined, use (.==.) and (./=.) instead

Fractional a => Fractional (CSignal clk a) 
Integral a => Integral (CSignal clk a)

WARNING: toInteger is undefined, use toInteger1 instead

Num a => Num (CSignal clk a) 
Ord a => Ord (CSignal clk a)

WARNING: compare, (<), (>=), (>), and (<=) are undefined, use compare1, (.<.), (.>=.), (.>.), and (.<=.) instead

(Num a, Ord a) => Real (CSignal clk a)

WARNING: toRational is undefined, use toRational1 instead

Show a => Show (CSignal clk a) 
Bits a => Bits (CSignal clk a)

WARNING: testBit and popCount are undefined, use testBit1 and popCount1 instead

FiniteBits a => FiniteBits (CSignal clk a) 
Default a => Default (CSignal clk a) 
Lift a => Lift (CSignal clk a) 
SaturatingNum a => SaturatingNum (CSignal clk a) 
ExtendingNum a b => ExtendingNum (CSignal clk a) (CSignal clk b) 
type AResult (CSignal clk a) (CSignal clk b) = CSignal clk (AResult a b) 
type MResult (CSignal clk a) (CSignal clk b) = CSignal clk (MResult a b) 

Clock domain crossing

Clock

data Clock Source

A clock with a name (Symbol) and period (Nat)

Constructors

Clk Symbol Nat 

data SClock clk where Source

Singleton value for a type-level Clock with the given name and period

Constructors

SClock :: SSymbol name -> SNat period -> SClock (Clk name period) 

sclock :: (KnownSymbol name, KnownNat period) => SClock (Clk name period) Source

Create a singleton clock

withSClock :: (KnownSymbol name, KnownNat period) => (SClock (Clk name period) -> a) -> a Source

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

veryUnsafeSynchronizer Source

Arguments

:: SClock clk1

Clock of the incoming signal

-> SClock clk2

Clock of the outgoing signal

-> CSignal clk1 a 
-> CSignal clk2 a 

The veryUnsafeSynchronizer 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
             -> CSignal clkA Bit -> CSignal clkB Bit
dualFlipFlop clkA clkB = cregister clkB low . cregister clkB low
                       . veryUnsafeSynchronizer clkA clkB

The veryUnsafeSynchronizer 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:

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,...

Basic circuit functions

csignal :: a -> CSignal clk a Source

Create a constant CSignal from a combinational value

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

cregister :: SClock 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

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock
>>> csampleN 3 (cregister clkA100 8 (fromList [1,2,3,4]))
[8,1,2]

cregEn :: SClock clk -> a -> CSignal clk Bool -> CSignal clk a -> CSignal clk a Source

Version of cregister that only updates its content when its second argument is asserted. So given:

type ClkA = Clk "A" 100
clkA :: SClock Clka
clkA = sclock

oscillate = cregister clkA False (not1 oscillate)
count     = cregEn clkA 0 oscillate (count + 1)

We get:

>>> csampleN 8 oscillate
[False,True,False,True,False,True,False,True]
>>> csampleN 8 count
[0,0,1,1,2,2,3,3]

Product/Signal isomorphism

class Bundle a where Source

Isomorphism between a CSignal of a product type (e.g. a tuple) and a product type of CSignals.

Instances of Bundle must satisfy the following laws:

bundle . unbundle = id
unbundle . bundle = id

Minimal complete definition

Nothing

Associated Types

type Unbundled clk a Source

Methods

bundle :: SClock clk -> Unbundled clk a -> CSignal clk a Source

Example:

bundle :: (CSignal clk a, CSignal clk b) -> CSignal clk (a,b)

However:

bundle :: CSignal clk Bit -> CSignal clk Bit

unbundle :: SClock clk -> CSignal clk a -> Unbundled clk a Source

Example:

unbundle :: CSignal clk (a,b) -> (CSignal clk a, CSignal clk b)

However:

unbundle :: CSignal clk Bit -> CSignal clk Bit

Instances

Bundle Bool 
Bundle Double 
Bundle Float 
Bundle Int 
Bundle Integer 
Bundle () 
Bundle (Maybe a) 
Bundle (Index n) 
Bundle (BitVector n) 
Bundle (Signed n) 
Bundle (Unsigned n) 
Bundle (Either a b) 
Bundle (a, b) 
KnownNat n => Bundle (Vec n a) 
Bundle (a, b, c) 
Bundle (Fixed rep int frac) 
Bundle (a, b, c, d) 
Bundle (a, b, c, d, e) 
Bundle (a, b, c, d, e, f) 
Bundle (a, b, c, d, e, f, g) 
Bundle (a, b, c, d, e, f, g, h) 

Simulation functions (not synthesisable)

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

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

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock
>>> csimulate (cregister clkA100 8) [1, 2, 3, ...
[8, 1, 2, 3, ...

NB: This function is not synthesisable

csimulateB Source

Arguments

:: (Bundle a, Bundle b) 
=> SClock clk1

Clock of the incoming signal

-> SClock clk2

Clock of the outgoing signal

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

Function to simulate

-> [a] 
-> [b] 

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

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock
>>> csimulateB clkA100 clkA100 (cunpack clkA100 . cregister clkA100 (8,8) . cpack clkA100) [(1,1), (2,2), (3,3), ...
[(8,8), (1,1), (2,2), (3,3), ...

NB: This function is not synthesisable

List <-> CSignal conversion (not synthesisable)

csample :: CSignal clk 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, ...

NB: This function is not synthesisable

csampleN :: Int -> CSignal clk 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]

NB: This function is not synthesisable

cfromList :: [a] -> CSignal clk 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.

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

NB: This function is not synthesisable