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

Safe HaskellNone
LanguageHaskell2010

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 CSignals synchronous signals, as opposed to the implicitly clocked Signals 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

cmealy 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

-> CSignal clk i -> CSignal 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

clk100 = Clock d100

topEntity :: CSignal 100 (Int, Int) -> CSignal 100 Int
topEntity = cmealy clk100 mac 0
>>> csimulate clk100 clk100 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 :: (CSignal 100 Int, CSignal 100 Int)
        -> (CSignal 100 Int, CSignal 100 Int)
        -> CSignal 100 Int
dualMac (a,b) (x,y) = s1 + s2
  where
    s1 = cmealy clk100 mac 0 (bundle clk100 (a,x))
    s2 = cmealy clk100 mac 0 (bundle clk100 (b,y))

cmealyB 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 cmealy 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 cmealy, we have to write:

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

Using cmealyB however we can write:

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

cregisterB :: 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)')

clk100 = Clock d100

rP :: (CSignal 100 Int, CSignal 100 Int) -> (CSignal 100 Int, CSignal 100 Int)
rP = cregisterB d100 (8,8)
>>> csimulateB clk100 clk100 rP [(1,1),(2,2),(3,3),...
[(8,8),(1,1),(2,2),(3,3),...

BlockRAM primitives

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

-> CSignal clk (Unsigned m)

Write address w

-> CSignal clk (Unsigned m)

Read address r

-> CSignal clk Bool

Write enable

-> CSignal clk a

Value to write (at address w)

-> CSignal 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 :: CSignal ClkA (Unsigned 6) -> CSignal ClkA (Unsigned 6)
       -> CSignal ClkA Bool -> CSignal ClkA Bit -> ClkA CSignal Bit
bram40 = cblockRam clkA100 (replicate d40 H)

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

-> CSignal clk (Unsigned n)

Write address w

-> CSignal clk (Unsigned n)

Read address r

-> CSignal clk Bool

Write enable

-> CSignal clk a

Value to write (at address w)

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

bramC32 :: CSignal ClkA (Unsigned 5) -> CSignal ClkA (Unsigned 5)
        -> CSignal ClkA Bool -> CSignal ClkA Bit -> CSignal ClkA Bit
bramC32 = cblockRamPow2 clkA100 (replicate d32 H)

Utility functions

cwindow Source

Arguments

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

Clock to which the incoming signal is synchronized

-> CSignal clk a

Signal to create a window over

-> Vec (n + 1) (CSignal clk a)

Window of at least size 1

Give a window over a CSignal

window4 :: Signal Int -> Vec 4 (Signal Int)
window4 = window
>>> csimulateB 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>,...

cwindowD Source

Arguments

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

Clock to which the incoming signal is synchronized

-> CSignal clk a

Signal to create a window over

-> Vec (n + 1) (CSignal clk a)

Window of at least size 1

Give a delayed window over a CSignal

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

cisRising Source

Arguments

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

Starting value

-> CSignal clk a 
-> CSignal clk Bool 

Give a pulse when the CSignal goes from minBound to maxBound

cisFalling Source

Arguments

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

Starting value

-> CSignal clk a 
-> CSignal clk Bool 

Give a pulse when the CSignal goes from maxBound to minBound

Testbench functions

csassert Source

Arguments

:: (Eq a, Show a) 
=> CSignal t a

Checked value

-> CSignal t a

Expected value

-> CSignal t b

Return valued

-> CSignal t b 

Compares the first two arguments for equality and logs a warning when they are not equal. The second argument is considered the expected value. This function simply returns the third argument unaltered as its result. This function is used by coutputVerifier.

This function is translated to the following VHDL:

csassert_block : block
begin
  -- pragma translate_off
  process(clk_t,reset_t,arg0,arg1) is
  begin
    if (rising_edge(clk_t) or rising_edge(reset_t)) then
      assert (arg0 = arg1) report ("expected: " & to_string (arg1) & \", actual: \" & to_string (arg0)) severity error;
    end if;
  end process;
  -- pragma translate_on
  result <= arg2;
end block;

And can, due to the pragmas, be used in synthesizable designs

cstimuliGenerator Source

Arguments

:: forall l clk a . KnownNat l 
=> SClock clk

Clock to which to synchronize the output signal

-> Vec l a

Samples to generate

-> CSignal 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 :: CSignal clkA Int
testInput = cstimuliGenerator clkA $(v [(1::Int),3..21])
>>> csample testInput
[1,3,5,7,9,11,13,15,17,19,21,21,21,...

coutputVerifier Source

Arguments

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

Clock to which the input signal is synchronized to

-> Vec l a

Samples to compare with

-> CSignal clk a

Signal to verify

-> CSignal 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 :: CSignal ClkA Int -> CSignal ClkA Bool
expectedOutput = coutputVerifier clkA $(v ([70,99,2,3,4,5,7,8,9,10]::[Int]))
>>> csample (expectedOutput (cfromList ([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