xilinx-lava-5.0.1.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 Combinators

Serial composition combinators

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

Serial composition with no layout

(>->) :: (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 mid-horizontal left to right layout

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

Serial composition with overly layout

Conditional shift for obstacle avoidance

condShift :: (Int -> Bool, Int -> Int) -> (Int -> Bool, Int -> Int) -> Out ()Source

Parallel composition combinators

hRepN :: 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

Vertical parallel composition of two circuits

maP :: (a -> Out b) -> [a] -> Out [b]Source

Vertical map of a circuit

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

mapPair maps a circuit over adajcent pairs of elements in a list

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

Horizontal parallel composition of two circuits

hmaP :: (a -> Out b) -> [a] -> Out [b]Source

Horizontal map of a circuit

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

Parallel composition of two circuit which have overlaid layout

par3Overlay :: (a -> Out ao) -> (b -> Out bo) -> (c -> Out co) -> (a, b, c) -> Out (ao, bo, co)Source

Parallel composition of three circuit which have overlaid layout

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

halveListToPair :: [a] -> ([a], [a])Source

halveListToPair will take a list and return a pair containing the two halves.

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

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

Chops a list into chunks formed as pairs

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

projectFst :: (a, b) -> Out aSource

projectSnd :: (a, b) -> Out bSource

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

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

inputBitVecLocal creates a local 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

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

outputBitVecKept creates a bit-vector local singal with a KEEP attribute set

data Dir Source

Constructors

To 
Downto 

Instances

data NetType Source

Constructors

BitType 
BitVec Int Dir Int 

Instances

type Bit = IntSource

colSource

Arguments

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

type of element circuit r

-> (a, [b])

input to the col

-> Out ([c], a)

output of the col

Place four sided tile comoponents in a colum

Generating a Lava netlist

overlayTile :: Out a -> Out aSource

overlayTile takes a circuit instantiation block and overlays all the the instantions.

middle :: (a -> Out c) -> ((c, d) -> Out e) -> (b -> Out d) -> (a, b) -> Out eSource

Place components in a horizontal middle arrangement

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

Functions for defining new LUT-based gates

lut1gate :: (Bool -> Bool) -> String -> Bit -> Out BitSource

Implements a user-defined 1 input combinational gate

lut2gate :: (Bool -> Bool -> Bool) -> String -> (Bit, Bit) -> Out BitSource

Implements a user defined two input combinational gate

lut2gate_l :: (Bool -> Bool -> Bool) -> String -> (Bit, Bit) -> Out BitSource

Implements a local user defined two input combinational gate

lut3gate :: (Bool -> Bool -> Bool -> Bool) -> String -> (Bit, Bit, Bit) -> Out BitSource

Implements a user defined three input combinational gate

lut4gate :: (Bool -> Bool -> Bool -> Bool -> Bool) -> String -> (Bit, Bit, Bit, Bit) -> Out BitSource

Implements a user defined four input combinational gate

lut5gate :: (Bool -> Bool -> Bool -> Bool -> Bool -> Bool) -> String -> (Bit, Bit, Bit, Bit, Bit) -> Out BitSource

Implements a user defined five input combinational gate

lut6gate :: (Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool) -> String -> (Bit, Bit, Bit, Bit, Bit, Bit) -> Out BitSource

Implements a user defined six input combinational 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.