york-lava-0.2: A library for digital circuit description.

Recipe

Contents

Description

A library for writing behavioural descriptions in York Lava, inspired by Page and Luk's "Compiling Occam into Field-Programmable Gate Arrays", Oxford Workshop on Field Programmable Logic and Applications, 1991. Features explicit clocking, signals as well as registers, shared procedure calls, and an optimiser. The implementation is short and sweet! Used in the implementation of the Reduceron, a graph reduction machine for Xilinx FPGAs.

To illustrate, consider the implementation of a sequential multiplier using the shift-and-add algorithm.

 import Lava
 import Recipe

We define a state type containing three registers: the two inputs to multiply, and the result of the multiplication.

 data Mult n = Mult { a, b, result :: Reg n }

A value of type Mult n is created by newMult.

 newMult :: N n => New (Mult n)
 newMult = return Mult `ap` newReg `ap` newReg `ap` newReg

The shift-and-add recipe operates over a value of type Mult n.

 shiftAndAdd s =
   While (s!b!val =/= 0) $
     Seq [ s!a <== s!a!val!shr
         , s!b <== s!b!val!shl
         , s!b!val!vhead |>
             s!result <== s!result!val + s!a!val
         , Tick
         ]
 shr x = low +> vinit x
 shl x = vtail x <+ low

Three remarks are in order:

  1. The ! operator is flipped application with a high precedence.
      infixl 9 !
      (!) :: a -> (a -> b) -> b
      x!f = f x

This gives descriptions an appropriate object-oriented flavour.

  1. The value of a variable is obtained using the function
      val :: Var v => v n -> Word n

Registers (of type Reg) are an instance of the Var class.

  1. The functions +> and <+ perform cons and snoc operations on vectors, vhead takes the head of a vector, and =/= is generic disequality.

To actually perform a multiplication, the input variables need to be initialised.

 multiply x y s =
   Seq [ s!a <== x, s!b <== y, s!result <== 0, Tick, s!shiftAndAdd ]
 example :: Mult N8 -> Recipe
 example s = s!multiply 5 25
 simExample = simRecipe newMult example result

Evaluating simExample yields 25 :: Word N8.

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

Synopsis

Recipe constructs

data Recipe Source

Constructors

Skip

The most basic recipe; does nothing.

Tick

Does nothing, but takes one clock-cycle to do it.

Seq [Recipe]

Sequential composition of recipes.

Par [Recipe]

Fork-Join parallel composition of recipes.

While Bit Recipe

Run a recipe while a condition holds.

Do Recipe Bit

Like While, but condition is checked at the end of each iteration.

(|>) :: Bit -> Recipe -> RecipeSource

Run a recipe only if a condition holds.

call :: Proc -> RecipeSource

Call a procedure.

class Var v whereSource

Mutable variables; named locations that can be read from and assigned to.

Methods

val :: v n -> Word nSource

Return the value of a variable of width n.

(<==) :: v n -> Word n -> RecipeSource

Assign a value to a variable of width n.

Instances

(!) :: a -> (a -> b) -> bSource

Reverse function application.

(-->) :: a -> b -> (a, b)Source

Infix constructor for pairs.

The New monad

type New a = RWS Schedule (Bit, Recipe) VarId aSource

It's a monad; that's all you need to know.

Mutable variables: registers and signals

data Reg n Source

Register variables: assignments to a register come into effect in the clock-cycle after the assignment is performed; the initial value of a register is zero unless otherwise specified.

Instances

Var Reg 
Show (Reg n) 
Generic (Reg n) 

newReg :: N n => New (Reg n)Source

newRegInit :: N n => Word n -> New (Reg n)Source

data Sig n Source

Signal variables: assignments to a signal come into effect in the current clock-cycle, but last only for the duration of that clock-cycle; if a signal not assigned to in a clock-cycle then its value will be its default value which is zero unless otherwise specified.

Instances

Var Sig 
Show (Sig n) 
Generic (Sig n) 

newSig :: N n => New (Sig n)Source

newSigDef :: N n => Word n -> New (Sig n)Source

Shared procedures

newProc :: Recipe -> New ProcSource

Capture a recipe as shared procedure that can be called whenever desired; needless to say, the programmer should avoid parallel calls to the same shared procedure!

Running recipes

recipeSource

Arguments

:: New a

A state creator

-> (a -> Recipe)

A recipe which manipulates the state

-> Bit

A start pulse

-> (a, Bit)

A finish pulse and the resulting state

Simulating recipes

simRecipeSource

Arguments

:: Generic b 
=> New a

A state creator

-> (a -> Recipe)

A recipe which manipulates the state

-> (a -> b)

A selector over the state

-> b

The part of the state you selected