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

Copyright(C) 2013-2016, University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • GADTs
  • GADTSyntax
  • DataKinds
  • MagicHash

CLaSH.Signal.Explicit

Contents

Description

 

Synopsis

Explicitly clocked synchronous signal

CλaSH supports explicitly clocked Signals 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 goes any faster!

data Signal' 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 (Signal' clk) Source 
Applicative (Signal' clk) Source 
Foldable (Signal' clk) Source

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 (Signal' clk) Source 
Bounded a => Bounded (Signal' clk a) Source 
Enum a => Enum (Signal' clk a) Source

WARNING: fromEnum is undefined, use fromEnum1 instead

Eq (Signal' clk a) Source

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

Fractional a => Fractional (Signal' clk a) Source 
Integral a => Integral (Signal' clk a) Source

WARNING: toInteger is undefined, use toInteger1 instead

Num a => Num (Signal' clk a) Source 
Ord a => Ord (Signal' clk a) Source

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

(Num a, Ord a) => Real (Signal' clk a) Source

WARNING: toRational is undefined, use toRational1 instead

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: testBit and popCount are undefined, use testBit1 and popCount1 instead

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

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) 

Instances

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

Create a singleton clock

type ClkA = Clk "A" 100

clkA :: SClock ClkA
clkA = sclock

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

freqCalc :: [Integer] -> [Integer] Source

Calculate relative periods given a list of frequencies.

So for example, you have one part of your design connected to an ADC running at 20 MHz, one part of your design connected to a DAC running at 36 MHz, and the rest of your system is running at 50 MHz. What are the relative (integer) clock periods in CλaSH, such that their ratios correspond to the ratios between the actual clock frequencies.

For this we use freqCalc:

>>> freqCalc [20,36,50]
[45,25,18]

So that we create the proper clocks:

type ADC20 = Clk "ADC" 45
type DAC36 = Clk "DAC" 25
type Sys50 = Clk "Sys" 18

sys50 :: SClock Sys50
sys50 = sclock

adc20 :: SClock ADC20
adc20 = sclock

dac36 :: SClock DAC36
dac36 = sclock

NB: This function is not synthesisable

Synchronisation primitive

unsafeSynchronizer Source

Arguments

:: SClock clk1

Clock of the incoming signal

-> SClock clk2

Clock of the outgoing signal

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

register' :: SClock clk -> a -> Signal' clk a -> Signal' clk a Source

"register' i s" delays the values in Signal' s for one cycle, and sets the value at time 0 to i

type ClkA = Clk "A" 100

clkA :: SClock ClkA
clkA = sclock
>>> sampleN 3 (register' clkA 8 (fromList [1,2,3,4]))
[8,1,2]

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

class Bundle a where Source

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

instance Bundle D where
  type Unbundled' clk D = Signal' clk D
  bundle'   _ s = s
  unbundle' _ s = s

Minimal complete definition

Nothing

Associated Types

type Unbundled' clk a Source

Methods

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' clk Bit -> Signal' clk Bit

unbundle' :: SClock clk -> Signal' clk a -> Unbundled' clk a Source

Example:

unbundle' :: Signal' clk (a,b) -> (Signal' clk a, Signal' clk b)

However:

unbundle' :: Signal' clk Bit -> Signal' clk Bit

Instances

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)

simulateB' 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 (Unbundled' clk1 a -> Unbundled' clk2 b) function given a list of samples of type a

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

Strict version

simulateB'_strict Source

Arguments

:: (Bundle a, Bundle b, NFData a, NFData 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] 

Deprecated: simulateB' will be strict in CLaSH 1.0, and simulateB'_strict will be removed

Version of simulateB' that strictly evaluates the input elements and the output elements

N.B: Exceptions are lazily rethrown