xilinx-lava-5.0.0.0: The Lava system for Xilinx FPGA design with layout combinators.

Lava

Contents

Description

Xilinx Lava is a library for FPGA circuit design with a focus on circuit layout.

Synopsis

Lava Gates

LUT-based gates

invSource

Arguments

:: Bit

The input i0

-> Out Bit

The output o

The inv function implements an invertor explicitly with a LUT1.

and2Source

Arguments

:: (Bit, Bit)

inputs (i0, i1)

-> Out Bit

output o

The and2 function implements an AND gate explicitly with a LUT2.

or2Source

Arguments

:: (Bit, Bit)

inputs (i0, i1)

-> Out Bit

output o

The or2 function implements an OR gate explicitly with a LUT2.

nor2Source

Arguments

:: (Bit, Bit)

inputs (i0, i1)

-> Out Bit

output o

The nor2 function implements an NOR gate explicitly with a LUT2.

xor2Source

Arguments

:: (Bit, Bit)

inputs (i0, i1)

-> Out Bit

output o

The xor2 function implements an XOR gate explicitly with a LUT2.

xnor2Source

Arguments

:: (Bit, Bit)

inputs (i0, i1)

-> Out Bit

output o

The xnor2 function implements an XOR gate explicitly with a LUT2.

Carry-chain elements

muxcySource

Arguments

:: Bit

ci

-> Bit

di

-> Bit

s

-> Out Bit

o

muxcy_d :: Bit -> Bit -> Bit -> Out (Bit, Bit)Source

muxf5_d :: Bit -> Bit -> Bit -> Out (Bit, Bit)Source

muxf6_d :: Bit -> Bit -> Bit -> Out (Bit, Bit)Source

muxf7_d :: Bit -> Bit -> Bit -> Out (Bit, Bit)Source

muxf8_d :: Bit -> Bit -> Bit -> Out (Bit, Bit)Source

Flip-flops

fdc :: Bit -> Bit -> Bit -> Out BitSource

fdce :: Bit -> Bit -> Bit -> Bit -> Out BitSource

fdce_1 :: Bit -> Bit -> Bit -> Bit -> Out BitSource

fdcp :: Bit -> Bit -> Bit -> Bit -> Out BitSource

fdcpe :: Bit -> Bit -> Bit -> Bit -> Bit -> Out BitSource

fdcpe_1 :: Bit -> Bit -> Bit -> Bit -> Bit -> Out BitSource

Shift-register primitives

srl16eSource

Arguments

:: Bit

d

-> Bit

clk

-> Bit

ce

-> Bit

a0

-> Bit

a1

-> Bit

a2

-> Bit

a3

-> Out Bit

q

16-bit shift register look-up table with clock enable

Gates implemented in place of a slice latch

and2b1lSource

Arguments

:: Bit

di

-> Bit

sri

-> Out Bit

o

Two input and gate implemented in place of a slice latch

or2lSource

Arguments

:: Bit

di

-> Bit

sri

-> Out Bit

o

Two input and gate implemented in place of a slice latch

Buffers

ibufgSource

Arguments

:: Bit

i

-> Out Bit

o

Dedicated input clock buffer

bufgSource

Arguments

:: Bit

i

-> Out Bit

o

Global clock buffer

bufgpSource

Arguments

:: Bit

i

-> Out Bit

o

Global clock buffer

obufgSource

Arguments

:: Bit

i

-> Out Bit

o

Output buffer

Double data rate (DDR) components

obufdsSource

Arguments

:: Bit

i

-> Out (Bit, Bit)

(o, ob)

Output buffer

Lava Combinators

Serial composition combinators

(>->) :: (a -> Out b) -> (b -> Out c) -> a -> Out cSource

Serial composition with horizontal left to right layout

(>|>) :: (a -> Out b) -> (b -> Out c) -> a -> Out cSource

Serial composition with overly layout

Parallel composition combinators

replicateHorizontal :: Int -> (a -> Out a) -> a -> Out aSource

Repeated serial composition (left to right)

par2 :: (a -> Out c) -> (b -> Out d) -> (a, b) -> Out (c, d)Source

Horizontal parallel composition of two circuits

hpar :: [a -> Out b] -> [a] -> Out [b]Source

Horizontal parallel composition of a list of circuits

hparN :: Int -> (a -> Out b) -> [a] -> Out [b]Source

Horizontal repeated parallel composition of a circuit

Wiring combinators

fork2 :: a -> Out (a, a)Source

Splits a wire into two

listToPair :: [a] -> Out (a, a)Source

Converts a two element list into a pair

pairToList :: (a, a) -> Out [a]Source

Converts a par into a list containing two elements

ziP :: ([a], [b]) -> Out [(a, b)]Source

Takes a pair of lists and returns a zipped list of pairs

unziP :: [(a, b)] -> Out ([a], [b])Source

Takes a list of pairs and unzips it into a pair of lists

zipList :: [[a]] -> Out [[a]]Source

Takes a list containing two elements and returns a list of lists where each element is a two element list

unzipList :: [[a]] -> Out [[a]]Source

Undo the zipList operation

fstListPair :: [a] -> aSource

sndListPair :: [a] -> aSource

pair :: [a] -> Out [[a]]Source

This makes pairs out of consequetive members of an even length list.

unpair :: [[a]] -> Out [a]Source

Takes a list of pairs and returns a flattend list

halve :: [a] -> Out ([a], [a])Source

Tales a list and returns a pair containing the two halves of the list

unhalve :: ([a], [a]) -> Out [a]Source

Take a pair containing two list halves and undoes the halve

halveList :: [a] -> Out [[a]]Source

Halves the input list into a list containign the two halves

unhalveList :: [[a]] -> Out [a]Source

Undoes halveList

chop :: Int -> [a] -> Out [[a]]Source

Chops a list into chunks

concaT :: [[a]] -> Out [a]Source

Takes a list of lists and returns their concatenation

fstList :: ([a] -> Out [a]) -> [a] -> Out [a]Source

Applies a circuit to the first halve of a list

sndList :: ([a] -> Out [a]) -> [a] -> Out [a]Source

Applies a circuit to the second halve of a list

fsT :: (a -> Out b) -> (a, c) -> Out (b, c)Source

Applies a circuit to the first element of a pair

snD :: (b -> Out c) -> (a, b) -> Out (a, c)Source

Applies a circuit to the second element of a pair

reversE :: [a] -> Out [a]Source

Circuit input/output ports

inputPort :: String -> NetType -> Out BitSource

inputPort creates a single bit input port

inputBitVec :: String -> NetType -> Out [Bit]Source

inputBitVec creates a bit-vector input port

outputPort :: String -> NetType -> Bit -> Out ()Source

outputPort creates a single bit output port

outputBitVec :: String -> NetType -> [Bit] -> Out ()Source

outputBitVec creates a bit-vector output port

data Dir Source

Constructors

To 
Downto 

Instances

data NetType Source

Constructors

BitType 
BitVec Int Dir Int 

Instances

type Bit = IntSource

Generating a Lava netlist

Adding new primitive gates to the Lava system

primitiveGateSource

Arguments

:: String

The name of the component

-> [(String, Bit)]

name of input ports with argument nets

-> [String]

name of output ports

-> Maybe (Int, Int)

optional size information for layout

-> Out [Bit]

a list of output nets from this component

primitiveGate adds a primitive gate

Getting the Lava version number

lavaVersion :: (Int, Int, Int, Int)Source

This function defines the version of Lava which should correspond to the Cabal version.