york-lava-0.1: A library for circuit description.

Lava.Bit

Contents

Description

Defines what a Bit is, the central abstract data type of the whole library, along with lots of things you might like to do with bits.

See REDUCERON MEMO 23 - included in the package and available at http://www.cs.york.ac.uk/fp/reduceron/ - for a tutorial.

Synopsis

Documentation

data Bit Source

The central ADT of Lava.

Instances

Eq Bit 
Num Bit 
Show Bit 
Generic Bit 
Eq (Vec n Bit) 
N n => Num (Vec n Bit) 
Ordered (Vec n Bit) 

Standard logic gates

low :: BitSource

Logic '0'.

high :: BitSource

Logic '1'.

inv :: Bit -> BitSource

Inverter.

delayBit :: Bit -> Bit -> BitSource

D-type flip-flop, with initialiser (first argument).

delayBitEn :: Bit -> Bit -> Bit -> BitSource

D-type flip-flop with input-enable (first argument).

and2 :: (Bit, Bit) -> BitSource

AND gate.

or2 :: (Bit, Bit) -> BitSource

OR gate.

xor2 :: (Bit, Bit) -> BitSource

XOR gate.

xorcy :: (Bit, Bit) -> BitSource

XOR gate, specifically a Xilinx Carry Logic XOR gate.

eq2 :: (Bit, Bit) -> BitSource

EQ gate.

muxBit :: Bit -> Bit -> Bit -> BitSource

Bit multiplexer.

muxcy :: Bit -> (Bit, Bit) -> BitSource

Bit multiplexer - specifically a Xilinx Carry Logic bit multiplexer.

name :: String -> BitSource

Named input - for synthesis.

RAMs

data RamInps Source

Block RAM inputs; data-bus and address-bus can be of any width! Use Lava.Prelude.RamInputs for stronger type-safety.

Constructors

RamInps 

Fields

dataBus :: [Bit]
 
addressBus :: [Bit]
 
writeEnable :: Bit
 

data RamAlgorithm Source

How should the RAM be built? Used by the Xilinx Core Generator - see Xilinx docs for details.

primRam :: [Integer] -> RamAlgorithm -> RamInps -> [Bit]Source

Single-port RAM with initialiser. Use Lava.Prelude.ram for stronger type-safety.

primDualRam :: [Integer] -> RamAlgorithm -> (RamInps, RamInps) -> ([Bit], [Bit])Source

Dual-port RAM with initialiser. Use Lava.Prelude.dualRam for stronger type-safety.

Generic operations over structures of bits

class Generic a whereSource

Generic structures of bits

Methods

generic :: a -> BitContainer aSource

Instances

Generic () 
Generic Bit 
Generic a => Generic [a] 
Generic a => Generic (Maybe a) 
Generic (Signed n) 
Generic (Reg n) 
Generic (Sig n) 
(Generic a, Generic b) => Generic (Either a b) 
(Generic a, Generic b) => Generic (a, b) 
Generic a => Generic (Vec n a) 
(Generic a, Generic b, Generic c) => Generic (a, b, c) 
(Generic a, Generic b, Generic c, Generic d) => Generic (a, b, c, d) 
(Generic a, Generic b, Generic c, Generic d, Generic e) => Generic (a, b, c, d, e) 
(Generic a, Generic b, Generic c, Generic d, Generic e, Generic f) => Generic (a, b, c, d, e, f) 
(Generic a, Generic b, Generic c, Generic d, Generic e, Generic f, Generic g) => Generic (a, b, c, d, e, f, g) 
(Generic a, Generic b, Generic c, Generic d, Generic e, Generic f, Generic g, Generic h) => Generic (a, b, c, d, e, f, g, h) 

type BitContainer a = (JList Bit, JList Bit -> a)Source

Basic idea pinched from Uniplate. To use generics, you really don't need to know the internals of this type as we provide cons and ><. For example:

 instance Generic a => Generic [a] where
    generic [] = cons []
    generic (a:as) = cons (:) >< a >< as

(><) :: Generic a => BitContainer (a -> b) -> a -> BitContainer bSource

structure :: Generic a => a -> JList BitSource

Extract a join-list of bits from any structure of bits.

bits :: Generic a => a -> [Bit]Source

Extract a list of bits from any structure of bits.

mapG :: Generic a => (Bit -> Bit) -> a -> aSource

Map a function over bits across any structure of bits.

zipWithG :: Generic a => (Bit -> Bit -> Bit) -> a -> a -> aSource

Zip a function over bits across any two structures of bits. Assumes that the two structures have the same shape.

lazyZipWithG :: Generic a => (Bit -> Bit -> Bit) -> a -> a -> aSource

A lazier but less-defined version of zipWithG.

Simulation

boolToBit :: Bool -> BitSource

Convert False to low and True to high.

simulate :: Generic a => a -> [a]Source

Simulate a circuit, giving the output on each clock-cycle. Returns an infinite list.

simulateN :: Generic a => Int -> a -> [a]Source

Simulate a circuit for N clock-cycles.

simulateSeq :: (Generic a, Generic b) => (a -> b) -> [a] -> [b]Source

Simulate a circuit with a constant waveform specified as input.

bitToBool :: Bit -> BoolSource

Simulate a circuit returning a single bit, and convert result to a boolean.

Netlist generation

data Net Source

Constructors

Net 

Instances

data Netlist Source

Constructors

Netlist 

Fields

namedOutputs :: [(String, Wire)]
 
nets :: [Net]
 

Instances

netlist :: Generic a => a -> a -> IO NetlistSource

Turn any circuit into a netlist.

Primitive component creation

makeComponentSource

Arguments

:: String

Component name

-> [Bit]

Inputs

-> Int

Number of outputs

-> ([Signal] -> [Signal])

Simulation function

-> [Parameter]

Component parameters

-> ([Bit] -> a)

Continuation (passed output bits)

-> a

Result

The programmer's interface to creating new primitive components. See definition of and2 for an example.

type Signal = [Bool]Source

A time-varying binary signal is clasically a list of booleans.

type InstanceId = IntSource

Every primitive component instance has a unique number.

type OutputNumber = IntSource

Each output from a primitive component is numbered.

type Wire = (InstanceId, OutputNumber)Source

A wire is uniquely identified by a instance id and an output number.

data Parameter Source

Components may have compile-time parameters, for example whether a flip-flop initialises to high or low. A parameter has a name and a value, both represented as strings.

Constructors

String :-> String 

Instances