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

Copyright(C) 2013-2015, University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010
Extensions
  • DataKinds
  • FlexibleContexts
  • TypeOperators
  • ExplicitNamespaces

CLaSH.Prelude.Explicit

Contents

Description

This module defines the explicitly clocked counterparts of the functions defined in CLaSH.Prelude.

This module uses the explicitly clocked Signal' synchronous signals, as opposed to the implicitly clocked Signal used in CLaSH.Prelude. Take a look at CLaSH.Signal.Explicit to see how you can make multi-clock designs using explicitly clocked signals.

Synopsis

Creating synchronous sequential circuits

mealy' Source

Arguments

:: SClock clk

Clock to synchronize to

-> (s -> i -> (s, o))

Transfer function in mealy machine form: state -> input -> (newstate,output)

-> s

Initial state

-> Signal' clk i -> Signal' clk o

Synchronous sequential function with input and output matching that of the mealy machine

Create a synchronous function from a combinational function describing a mealy machine

mac :: Int        -- Current state
    -> (Int,Int)  -- Input
    -> (Int,Int)  -- (Updated state, output)
mac s (x,y) = (s',s)
  where
    s' = x * y + s

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock

topEntity :: Signal' ClkA (Int, Int) -> Signal' ClkA Int
topEntity = mealy' clkA100 mac 0
>>> simulate topEntity [(1,1),(2,2),(3,3),(4,4),...
[0,1,5,14,30,...

Synchronous sequential functions can be composed just like their combinational counterpart:

dualMac :: (Signal' clkA100 Int, Signal' clkA100 Int)
        -> (Signal' clkA100 Int, Signal' clkA100 Int)
        -> Signal' clkA100 Int
dualMac (a,b) (x,y) = s1 + s2
  where
    s1 = mealy' clkA100 mac 0 (bundle' clkA100 (a,x))
    s2 = mealy' clkA100 mac 0 (bundle' clkA100 (b,y))

mealyB' Source

Arguments

:: (Bundle i, Bundle o) 
=> SClock clk 
-> (s -> i -> (s, o))

Transfer function in mealy machine form: state -> input -> (newstate,output)

-> s

Initial state

-> Unbundled' clk i -> Unbundled' clk o

Synchronous sequential function with input and output matching that of the mealy machine

A version of mealy' that does automatic Bundleing

Given a function f of type:

f :: Int -> (Bool,Int) -> (Int,(Int,Bool))

When we want to make compositions of f in g using mealy', we have to write:

g clk a b c = (b1,b2,i2)
  where
    (i1,b1) = unbundle' clk (mealy' clk f 0 (bundle' clk (a,b)))
    (i2,b2) = unbundle' clk (mealy' clk f 3 (bundle' clk (i1,c)))

Using mealyB' however we can write:

g clk a b c = (b1,b2,i2)
  where
    (i1,b1) = mealyB' clk f 0 (a,b)
    (i2,b2) = mealyB' clk f 3 (i1,c)

registerB' :: Bundle a => SClock clk -> a -> Unbundled' clk a -> Unbundled' clk a Source

Create a register function for product-type like signals (e.g. (Signal a, Signal b))

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock

rP :: (Signal' ClkA Int, Signal' ClkA Int) -> (Signal' ClkA Int, Signal' ClkA Int)
rP = registerB' clkA100 (8,8)
>>> simulateB' rP [(1,1),(2,2),(3,3),...
[(8,8),(1,1),(2,2),(3,3),...

BlockRAM primitives

blockRam' Source

Arguments

:: (KnownNat n, KnownNat m) 
=> SClock clk

Clock to synchronize to

-> Vec n a

Initial content of the BRAM, also determines the size, n, of the BRAM.

NB: MUST be a constant.

-> Signal' clk (Unsigned m)

Write address w

-> Signal' clk (Unsigned m)

Read address r

-> Signal' clk Bool

Write enable

-> Signal' clk a

Value to write (at address w)

-> Signal' clk a

Value of the blockRAM at address r from the previous clock cycle

Create a blockRAM with space for n elements

  • NB: Read value is delayed by 1 cycle
  • NB: Initial output value is undefined
type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock

bram40 :: Signal' ClkA (Unsigned 6) -> Signal' ClkA (Unsigned 6)
       -> Signal' ClkA Bool -> Signal' ClkA Bit -> ClkA Signal' Bit
bram40 = blockRam' clkA100 (replicate d40 1)

blockRamPow2' Source

Arguments

:: (KnownNat n, KnownNat (2 ^ n)) 
=> SClock clk

Clock to synchronize to

-> Vec (2 ^ n) a

Initial content of the BRAM, also determines the size, 2^n, of the BRAM.

NB: MUST be a constant.

-> Signal' clk (Unsigned n)

Write address w

-> Signal' clk (Unsigned n)

Read address r

-> Signal' clk Bool

Write enable

-> Signal' clk a

Value to write (at address w)

-> Signal' clk a

Value of the blockRAM at address r from the previous clock cycle

Create a blockRAM with space for 2^n elements

  • NB: Read value is delayed by 1 cycle
  • NB: Initial output value is undefined
type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock

bram32 :: Signal' ClkA (Unsigned 5) -> Signal' ClkA (Unsigned 5)
       -> Signal' ClkA Bool -> Signal' ClkA Bit -> Signal' ClkA Bit
bram32 = blockRamPow2' clkA100 (replicate d32 1)

Utility functions

window' Source

Arguments

:: (KnownNat n, Default a) 
=> SClock clk

Clock to which the incoming signal is synchronized

-> Signal' clk a

Signal to create a window over

-> Vec (n + 1) (Signal' clk a)

Window of at least size 1

Give a window over a Signal'

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock

window4 :: Signal' ClkA Int -> Vec 4 (Signal' ClkA Int)
window4 = window' clkA100
>>> simulateB' clkA100 clkA100 window4 [1,2,3,4,5,...
[<1,0,0,0>, <2,1,0,0>, <3,2,1,0>, <4,3,2,1>, <5,4,3,2>,...

windowD' Source

Arguments

:: (KnownNat (n + 1), Default a) 
=> SClock clk

Clock to which the incoming signal is synchronized

-> Signal' clk a

Signal to create a window over

-> Vec (n + 1) (Signal' clk a)

Window of at least size 1

Give a delayed window over a Signal'

type ClkA = Clk "A" 100

clkA100 :: SClock ClkA
clkA100 = sclock

windowD3 :: Signal' ClkA Int -> Vec 3 (Signal' ClkA Int)
windowD3 = windowD
>>> simulateB' clkA100 clkA100 windowD3 [1,2,3,4,...
[<0,0,0>, <1,0,0>, <2,1,0>, <3,2,1>, <4,3,2>,...

isRising' Source

Arguments

:: (Bounded a, Eq a) 
=> SClock clk 
-> a

Starting value

-> Signal' clk a 
-> Signal' clk Bool 

Give a pulse when the Signal' goes from minBound to maxBound

isFalling' Source

Arguments

:: (Bounded a, Eq a) 
=> SClock clk 
-> a

Starting value

-> Signal' clk a 
-> Signal' clk Bool 

Give a pulse when the Signal' goes from maxBound to minBound

Testbench functions

stimuliGenerator' Source

Arguments

:: KnownNat l 
=> SClock clk

Clock to which to synchronize the output signal

-> Vec l a

Samples to generate

-> Signal' clk a

Signal of given samples

To be used as a one of the functions to create the "magical" testInput value, which the CλaSH compilers looks for to create the stimulus generator for the generated VHDL testbench.

Example:

type ClkA = Clk "A" 100

clkA :: SClock ClkA
clkA = sclock

testInput :: Signal' clkA Int
testInput = stimuliGenerator' clkA $(v [(1::Int),3..21])
>>> sample testInput
[1,3,5,7,9,11,13,15,17,19,21,21,21,...

outputVerifier' Source

Arguments

:: (KnownNat l, Eq a, Show a) 
=> SClock clk

Clock to which the input signal is synchronized to

-> Vec l a

Samples to compare with

-> Signal' clk a

Signal to verify

-> Signal' clk Bool

Indicator that all samples are verified

To be used as a functions to generate the "magical" expectedOutput function, which the CλaSH compilers looks for to create the signal verifier for the generated VHDL testbench.

Example:

type ClkA = Clk "A" 100

clkA :: SClock ClkA
clkA = sclock

expectedOutput :: Signal' ClkA Int -> Signal' ClkA Bool
expectedOutput = outputVerifier' clkA $(v ([70,99,2,3,4,5,7,8,9,10]::[Int]))
>>> sample (expectedOutput (fromList ([0..10] ++ [10,10,10])))
[
expected value: 70, not equal to actual value: 0
False,
expected value: 99, not equal to actual value: 1
False,False,False,False,False,
expected value: 7, not equal to actual value: 6
False,
expected value: 8, not equal to actual value: 7
False,
expected value: 9, not equal to actual value: 8
False,
expected value: 10, not equal to actual value: 9
False,True,True,...

Exported modules

Explicitly clocked synchronous signals