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

Safe HaskellNone
LanguageHaskell2010

CLaSH.Prelude

Contents

Synopsis

Creating synchronous sequential circuits

(<^>) Source

Arguments

:: (Pack i, Pack o) 
=> (s -> i -> (s, o))

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

-> s

Initial state

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

topEntity :: (Signal Int, Signal Int) -> Signal Int
topEntity = mac <^> 0

simulateP 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 Int, Signal Int)
        -> (Signal Int, Signal Int)
        -> Signal Int
dualMac (a,b) (x,y) = s1 + s2
  where
    s1 = (mac <^> 0) (a,b)
    s2 = (mac <^> 0) (x,y)

registerP :: Pack a => a -> SignalP a -> SignalP a Source

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

rP :: (Signal Int,Signal Int) -> (Signal Int, Signal Int)
rP = registerP (8,8)

simulateP rP [(1,1),(2,2),(3,3),... == [(8,8),(1,1),(2,2),(3,3),...

Arrow interface for synchronous sequential circuits

newtype Comp a b Source

Component: an Arrow interface to synchronous sequential functions

Constructors

C 

Fields

asFunction :: Signal a -> Signal b
 

(^^^) Source

Arguments

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

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

-> s

Initial state

-> Comp i o

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

Create a synchronous Component 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

topEntity :: Comp (Int,Int) Int
topEntity = mac ^^^ 0

simulateC topEntity [(1,1),(2,2),(3,3),(4,4),... == [0,1,5,14,30,...

Synchronous sequential must be composed using the Arrow syntax

dualMac :: Comp (Int,Int,Int,Int) Int
dualMac = proc (a,b,x,y) -> do
  rec s1 <- mac ^^^ 0 -< (a,b)
      s2 <- mac ^^^ 0 -< (x,y)
  returnA -< (s1 + s2)

registerC :: a -> Comp a a Source

Create a register Component

rC :: Comp (Int,Int) (Int,Int)
rC = registerC (8,8)

simulateC rP [(1,1),(2,2),(3,3),... == [(8,8),(1,1),(2,2),(3,3),...

simulateC :: Comp a b -> [a] -> [b] Source

Simulate a Component given a list of samples

simulateC (registerC 8) [1, 2, 3, ... == [8, 1, 2, 3, ...

BlockRAM primitives

blockRam Source

Arguments

:: forall n m a . (KnownNat n, KnownNat m, Pack a) 
=> SNat n

Size n of the blockram

-> Signal (Unsigned m)

Write address w

-> Signal (Unsigned m)

Read address r

-> Signal Bool

Write enable

-> Signal a

Value to write (at address w)

-> Signal a

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

Create a blockRAM with space for n elements

bram40 :: Signal (Unsigned 6) -> Signal (Unsigned 6) -> Signal Bool -> Signal a -> Signal a
bram40 = blockRam d50

blockRamPow2 Source

Arguments

:: (KnownNat n, KnownNat (2 ^ n), Pack a) 
=> SNat (2 ^ n :: Nat)

Size 2^n of the blockram

-> Signal (Unsigned n)

Write address w

-> Signal (Unsigned n)

Read address r

-> Signal Bool

Write enable

-> Signal a

Value to write (at address w)

-> Signal a

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

Create a blockRAM with space for 2^n elements

bram32 :: Signal (Unsigned 5) -> Signal (Unsigned 5) -> Signal Bool -> Signal a -> Signal a
bram32 = blockRamPow2 d32

blockRamC Source

Arguments

:: (KnownNat n, KnownNat m, Pack a) 
=> SNat n

Size n of the blockram

-> Comp (Unsigned m, Unsigned m, Bool, a) a 

Create a blockRAM with space for n elements

bramC40 :: Comp (Unsigned 6, Unsigned 6, Bool, a) a
bramC40 = blockRamC d50

blockRamPow2C Source

Arguments

:: (KnownNat n, KnownNat (2 ^ n), Pack a) 
=> SNat (2 ^ n :: Nat)

Size 2^n of the blockram

-> Comp (Unsigned n, Unsigned n, Bool, a) a 

Create a blockRAM with space for 2^n elements

bramC32 :: Comp (Unsigned 5, Unsigned 5, Bool, a) a
bramC32 = blockRamPow2C d32

Utility functions

window :: (KnownNat (n + 1), Default a) => Signal a -> Vec ((n + 1) + 1) (Signal a) Source

Give a window over a Signal

window4 :: Signal Int -> Vec 4 (Signal Int)
window4 = window

simulateP window4 [1,2,3,4,5,... == [1:>0:>0:>0:>Nil, 2:>1:>0:>0:>Nil, 3:>2:>1:>0:>Nil, 4:>3:>2:>1:>Nil, 5:>4:>3:>2:>Nil,...

windowD :: (KnownNat (n + 1), Default a) => Signal a -> Vec (n + 1) (Signal a) Source

Give a delayed window over a Signal

windowD3 :: Signal Int -> Vec 3 (Signal Int)
windowD3 = windowD

simulateP windowD3 [1,2,3,4,... == [0:>0:>0:>Nil, 1:>0:>0:>Nil, 2:>1:>0:>Nil, 3:>2:>1:>Nil, 4:>3:>2:>Nil,...