Copyright | (C) 2013-2015, University of Twente |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Extensions |
|
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.
- mealy' :: SClock clk -> (s -> i -> (s, o)) -> s -> Signal' clk i -> Signal' clk o
- mealyB' :: (Bundle i, Bundle o) => SClock clk -> (s -> i -> (s, o)) -> s -> Unbundled' clk i -> Unbundled' clk o
- moore' :: SClock clk -> (s -> i -> s) -> (s -> o) -> s -> Signal' clk i -> Signal' clk o
- mooreB' :: (Bundle i, Bundle o) => SClock clk -> (s -> i -> s) -> (s -> o) -> s -> Unbundled' clk i -> Unbundled' clk o
- registerB' :: Bundle a => SClock clk -> a -> Unbundled' clk a -> Unbundled' clk a
- blockRam' :: (KnownNat n, KnownNat m) => SClock clk -> Vec n a -> Signal' clk (Unsigned m) -> Signal' clk (Unsigned m) -> Signal' clk Bool -> Signal' clk a -> Signal' clk a
- blockRamPow2' :: (KnownNat n, KnownNat (2 ^ n)) => SClock clk -> Vec (2 ^ n) a -> Signal' clk (Unsigned n) -> Signal' clk (Unsigned n) -> Signal' clk Bool -> Signal' clk a -> Signal' clk a
- window' :: (KnownNat n, Default a) => SClock clk -> Signal' clk a -> Vec (n + 1) (Signal' clk a)
- windowD' :: (KnownNat (n + 1), Default a) => SClock clk -> Signal' clk a -> Vec (n + 1) (Signal' clk a)
- isRising' :: (Bounded a, Eq a) => SClock clk -> a -> Signal' clk a -> Signal' clk Bool
- isFalling' :: (Bounded a, Eq a) => SClock clk -> a -> Signal' clk a -> Signal' clk Bool
- stimuliGenerator' :: forall l clk a. KnownNat l => SClock clk -> Vec l a -> Signal' clk a
- outputVerifier' :: forall l clk a. (KnownNat l, Eq a, Show a) => SClock clk -> Vec l a -> Signal' clk a -> Signal' clk Bool
- module CLaSH.Signal.Explicit
Creating synchronous sequential circuits
:: SClock clk |
|
-> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> 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 clkA ::SClock
ClkA clkA =sclock
topEntity ::Signal'
ClkA (Int, Int) ->Signal'
ClkA Int topEntity =mealy'
clkA mac 0
>>>
simulate topEntity [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14...
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))
:: (Bundle i, Bundle o) | |
=> SClock clk | |
-> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> 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 Bundle
ing
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)
:: SClock clk |
|
-> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Signal' clk i -> Signal' clk o | Synchronous sequential function with input and output matching that of the moore machine |
Create a synchronous function from a combinational function describing a moore machine
mac :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- Updated state mac s (x,y) = x * y + s type ClkA =Clk
"A" 100 clkA ::SClock
ClkA clkA =sclock
topEntity ::Signal'
ClkA (Int, Int) ->Signal'
ClkA Int topEntity =moore'
clkA mac id 0
>>>
simulate topEntity [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: (Signal'
clkA Int,Signal'
clkA Int) -> (Signal'
clkA Int,Signal'
clkA Int) ->Signal'
clkA Int dualMac (a,b) (x,y) = s1 + s2 where s1 =moore'
clkA mac id 0 (bundle'
clkA (a,x)) s2 =moore'
clkA mac id 0 (bundle'
clkA (b,y))
:: (Bundle i, Bundle o) | |
=> SClock clk | |
-> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Unbundled' clk i -> Unbundled' clk o | Synchronous sequential function with input and output matching that of the moore machine |
A version of moore'
that does automatic Bundle
ing
Given a functions t
and o
of types:
t :: Int -> (Bool, Int) -> Int o :: Int -> (Int, Bool)
When we want to make compositions of t
and o
in g
using moore'
, we have to
write:
g clk a b c = (b1,b2,i2) where (i1,b1) =unbundle'
clk (moore' clk t o 0 (bundle'
clk (a,b))) (i2,b2) =unbundle'
clk (moore' clk t o 3 (bundle'
clk (i1,c)))
Using mooreB'
however we can write:
g clk a b c = (b1,b2,i2) where (i1,b1) =mooreB'
clk t o 0 (a,b) (i2,b2) =mooreB'
clk to 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 clkA ::SClock
ClkA clkA =sclock
rP :: (Signal'
ClkA Int,Signal'
ClkA Int) -> (Signal'
ClkA Int,Signal'
ClkA Int) rP =registerB'
clkA (8,8)
>>>
simulateB' clkA clkA rP [(1,1),(2,2),(3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)...
BlockRAM primitives
:: (KnownNat n, KnownNat m) | |
=> SClock clk |
|
-> Vec n a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal' clk (Unsigned m) | Write address |
-> Signal' clk (Unsigned m) | Read address |
-> Signal' clk Bool | Write enable |
-> Signal' clk a | Value to write (at address |
-> Signal' clk a | Value of the |
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'
ClkABit
-> ClkASignal'
Bit
bram40 =blockRam'
clkA100 (replicate
d40 1)
:: (KnownNat n, KnownNat (2 ^ n)) | |
=> SClock clk |
|
-> Vec (2 ^ n) a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal' clk (Unsigned n) | Write address |
-> Signal' clk (Unsigned n) | Read address |
-> Signal' clk Bool | Write enable |
-> Signal' clk a | Value to write (at address |
-> Signal' clk a | Value of the |
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'
ClkABit
-> Signal' ClkABit
bram32 =blockRamPow2'
clkA100 (replicate
d32 1)
Utility functions
Testbench functions
:: 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])
>>>
sampleN 13 testInput'
[1,3,5,7,9,11,13,15,17,19,21,21,21]
:: (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]))
>>>
import qualified Data.List as List
>>>
sampleN 12 (expectedOutput' (fromList ([0..10] List.++ [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
module CLaSH.Signal.Explicit