• 设为首页
  • 点击收藏
  • 手机版
    手机扫一扫访问
    迪恩网络手机版
  • 关注官方公众号
    微信扫一扫关注
    迪恩网络公众号

blarney-lang/blarney: Haskell library for hardware description

原作者: [db:作者] 来自: 网络 收藏 邀请

开源软件名称(OpenSource Name):

blarney-lang/blarney

开源软件地址(OpenSource Url):

https://github.com/blarney-lang/blarney

开源编程语言(OpenSource Language):

Haskell 88.8%

开源软件介绍(OpenSource Introduction):

Blarney logo

Blarney is a Haskell library for hardware description that builds a range of HDL abstractions on top of a small set of pure functional circuit primitives. It is a modern variant of Lava with Verilog and SMT backends. Some aspects of the library are also inspired by Bluespec, such as first-class actions and method-based interfaces. Applications of Blarney include SIMTight (a CHERI-enabled RISC-V GPGPU) and Actora (a stack machine with a compiler for an Erlang-like language). Below, we introduce the library by example, supplementing the Haddock docs.

Contents

1. Prerequisites

We’ll need Verilator and GHC 9.2.1 or later.

On Ubuntu 20.04, we can do:

$ sudo apt install verilator

For GHC 9.2.1 or later, ghcup can be used.

2. Quick start

Recursively clone the repo and set the BLARNEY_ROOT environment variable to point to it, and add the Scripts directory to your PATH:

$ git clone --recursive https://github.com/blarney-lang/blarney
$ export BLARNEY_ROOT=$(pwd)/blarney
$ export PATH=$PATH:$BLARNEY_ROOT/Scripts

To run an example using Blarney’s in-Haskell simulator:

$ cd Examples/Sorter
$ make
$ ./Sorter --simulate

You should see the output:

sort [3,4,1,0,2] = [0,1,2,3,4]

To generate Verilog for an example, and then simulate the Verilog using Verilator, omit the --simulate option and then run the generated makefile:

$ ./Sorter             # Run the Verilog generator
$ cd Sorter-Verilog
$ make                 # Compile the generated Verilog using Verilator
$ ./Sorter             # Simulate the generated Verilog

You should see the same output as before. Using Verilator is the recommended approach for simulating Blarney designs.

To run the regression test suite:

$ cd Test
$ ./test.sh --run-all

3. Blarney by example

3.1. Two-sort

Sorting makes for a good introduction to the library. Let’s start with the simplest kind of sorter possible: given a pair of 8-bit values, the function twoSort returns the sorted pair.

import Blarney

twoSort :: (Bit 8, Bit 8) -> (Bit 8, Bit 8)
twoSort (a, b) = a .<. b ? ((a, b), (b, a))

This definition makes use of three Blarney constructs: the Bit type for bit vectors (parametised by the size of the vector); the comparison operator .<.; and the ternary conditional operator ?. A quick test bench to check that it works:

top :: Module ()
top = always do
  display "twoSort (1,2) = " (twoSort (1,2))
  display "twoSort (2,1) = " (twoSort (2,1))
  finish

We use Blarney’s always construct to perform the given action on every clock cycle. Blarney actions include statements for displaying values during simulation (display), terminating the simulator (finish), and mutating state (see below). All statements in an Action execute in parallel, within a single cycle of an implicit clock. We can generate Verilog for the test bench as follows.

main :: IO ()
main = writeVerilogTop top "top" "/tmp/twoSort/"

Assuming the above code is in a file named Sorter.hs, it can be compiled at the command-line using

$ blc Sorter.hs

where blc stands for Blarney compiler. This is just a script (from Blarney’s Scripts directory) that invokes GHC with the appropriate compiler flags. Running the resulting executable ./Sorter will produce Verilog in the /tmp/twoSort directory, including a makefile to build a Verilator simulator. The simulator can be built and run as follows.

$ cd /tmp/twoSort
$ make
$ ./top
twoSort (1,2) = (1,2)
twoSort (2,1) = (1,2)

3.2. In-Haskell simulation

Sometimes it can be convenient to skip Verilog generation, and use the in-Haskell simulator.

main :: IO ()
main = simulate top

Now after running ./Sorter we see the test bench output directly.

$ ./Sorter
twoSort (1,2) = (1,2)
twoSort (2,1) = (1,2)

The in-Haskell simulator is much slower than Verilator, but can be more convenient for small designs. It is currently an experimental feature.

3.3. Bubble sort

We can build a general N-element sorter by connecting together multiple two-sorters. One of the simplest ways to do this is the bubble sort network. The key component is a function bubble that takes a list of inputs and returns a new list in which the smallest element comes first.

bubble :: [Bit 8] -> [Bit 8]
bubble [] = []
bubble [x] = [x]
bubble (x:y:rest) = bubble (small:rest) ++ [large]
  where (small, large) = twoSort (x, y)

If we repeatedly call bubble then we end up with a sorted list.

sort :: [Bit 8] -> [Bit 8]
sort [] = []
sort xs = smallest : sort rest
  where smallest:rest = bubble xs

Running the test bench

top :: Module ()
top = always do
  let inputs = [3, 4, 1, 0, 2]
  display "sort " inputs " = " (sort inputs)
  finish

in simulation yields:

sort [3,4,1,0,2] = [0,1,2,3,4]

To see that the sort function really is describing a circuit, let’s draw the circuit digram for a 5-element bubble sorter.

        -->.
           |
        -->+---.
           |   |
Inputs  -->+---+---.
           |   |   |
        -->+---+---+---.
           |   |   |   |
        -->+---+---+---+---.
           |   |   |   |   |
           v   v   v   v   v

                Outputs

The input list is supplied on the left, and the sorted output list is produced at the bottom. Each + denotes a two-sorter that takes inputs from the top and the left, and produces the smaller value to the bottom and the larger value to the right. See The design and verification of a sorter core for a more in-depth exploration of sorting circuits in Haskell.

3.4. Polymorphism

For simplicity, we’ve made our sorter specific to lists of 8-bit values. But if we look at the types of the primitive functions it uses, we can see that it actually has a more general type.

(.<.) :: Cmp a  => a -> a -> Bit 1
(?)   :: Bits a => Bit 1 -> (a, a) -> a

So .<. can be used on any type in the Cmp (comparator) class. Similarly, ? can be used on any type in the Bits class (which allows packing to a bit vector and back again). So a more generic definition of twoSort would be:

twoSort :: (Bits a, Cmp a) => (a, a) -> (a, a)
twoSort (a, b) = a .<. b ? ((a, b), (b, a))

Indeed, this would be the type inferred by the Haskell compiler if no type signature was supplied. Using Haskell’s rebindable syntax, we can also use an if-then-else expression instead of the ternary conditional operator:

twoSort :: (Bits a, Cmp a) => (a, a) -> (a, a)
twoSort (a, b) = if a .<. b then (a, b) else (b, a)

3.5. Mutable registers

So far, we’ve only seen display and finish actions inside a Blarney module. Also supported are creation and assignment of registers. To illustrate, here is a module that creates a 4-bit cycleCount register, increments it on each cycle, stopping when it reaches 10.

top :: Module ()
top = do
  -- Create a register
  cycleCount :: Reg (Bit 4) <- makeReg 0

  always do
    -- Increment on every cycle
    cycleCount <== cycleCount.val + 1

    -- Display value on every cycle
    display "cycleCount = " cycleCount.val

    -- Terminate simulation when count reaches 10
    when (cycleCount.val .==. 10) do
      display "Finished"
      finish

This example introduces a number of new library functions: makeReg creates a register, initialised to the given value; the val field yeilds the current value of the register; and when allows conditional actions to be introduced. We can use if-then-else in an Action context. For example, the final three lines above could have been written as:

  -- Terminate simulation when count reaches 10
  if cycleCount.val .==. 10
    then do
      display "Finished"
      finish
    else
      display "Not finished"

Running top in simulation gives

cycleCount = 0
cycleCount = 1
cycleCount = 2
cycleCount = 3
cycleCount = 4
cycleCount = 5
cycleCount = 6
cycleCount = 7
cycleCount = 8
cycleCount = 9
cycleCount = 10
Finished

3.6. Queues

Queues (also known as FIFOs) are a commonly used abstraction in hardware design. Blarney provides a range of different queue implementations, all of which implement the following interface available when importing Blarney.Queue.

-- Queue interface
data Queue a =
  Queue {
    notEmpty :: Bit 1           -- Is the queue non-empty?
  , notFull  :: Bit 1           -- Is there any space in the queue?
  , enq      :: a -> Action ()  -- Insert an element (assuming notFull)
  , deq      :: Action ()       -- Remove the first element (assuming canDeq)
  , canDeq   :: Bit 1           -- Guard on the deq and first methods
  , first    :: a               -- View the first element (assuming canDeq)
  }

The type Queue a represents a queue holding elements of type a, and provides a range of standard functions on queues. The enq method should only be called when notFull is true and the deq method should only be called when canDeq is true. Similarly, the first element of the queue is only valid when canDeq is true. Below, we present the simplest possible implementation of a one-element queue.

import Blarney.Queue

-- Simple one-element queue implementation
makeSimpleQueue :: Bits a => Module (Queue a)
makeSimpleQueue = do
  -- Register holding the one element
  reg :: Reg a <- makeReg dontCare

  -- Register defining whether or not queue is full
  full :: Reg (Bit 1) <- makeReg 0

  -- Methods
  return
    Queue {
      notFull  = full.val .==. 0
    , notEmpty = full.val .==. 1
    , enq      = \a -> do reg <== a
                          full <== 1
    , deq      = full <== 0
    , canDeq   = full.val .==. 1
    , first    = reg.val
    }

The following simple test bench illustrates how to use a queue.

-- Small test bench for queues
top :: Module ()
top = do
  -- Instantiate a queue of 8-bit values
  queue :: Queue (Bit 8) <- makeSimpleQueue

  -- Create an 8-bit count register
  count :: Reg (Bit 8) <- makeReg 0

  always do
    count <== count.val + 1

    -- Writer side
    when queue.notFull do
      queue.enq count.val
      display "Enqueued " count.val

    -- Reader side
    when queue.canDeq do
      queue.deq
      display "Dequeued " queue.first

    -- Terminate after 100 cycles
    when (count.val .==. 100) finish

3.7. Mutable wires

Wires are a feature of the Action monad that offer a way for separate action blocks to communicate within the same clock cycle. Whereas assignment to a register becomes visible on the clock cycle after the assigment occurs, assignment to a wire is visible on the same cycle as the assignment. If no assignment is made to a wire on a particular cycle, then the wire emits its default value on that cycle. When multiple assignments to the same wire occur on the same cycle, the wire emits the bitwise disjunction of all the assigned values.

To illustrate, let’s implement an n-bit counter module that supports increment and decrement operations.

-- Interface for a n-bit counter
data Counter n =
  Counter {
    inc    :: Action ()
  , dec    :: Action ()
  , output :: Bit n
  }

We’d like the counter to support parallel calls to inc and dec. That is, if inc and dec are called on the same cycle then the counter’s output is unchanged. We’ll achieve this using wires.

makeCounter :: KnownNat n => Module (Counter n)
makeCounter = do
  -- State
  count :: Reg (Bit n) <- makeReg 0

  -- Wires
  incWire :: Wire (Bit 1) <- makeWire 0
  decWire :: Wire (Bit 1) <- makeWire 0

  always do
    -- Increment
    when (incWire.val .&&. inv decWire.val) do
      count <== count.val + 1

    -- Decrement
    when (inv incWire.val .&&. decWire.val) do
      count <== count.val - 1

  -- Interface
  return
    Counter {
      inc = do incWire <== 1
      dec = do decWire <== 1
      output = count.val
    }

3.8. Recipes

State machines are a common way of defining the control-path of a circuit. They are typically expressed by doing case-analysis of the current state and manually setting the next state. Quite often however, they can be expressed more neatly in a Recipe — a simple imperative language with various control-flow constructs.

data Recipe =
    Skip                         -- Do nothing (in zero cycles)
  | Tick                         -- Do nothing (in one cycle)
  | Action (Action ())           -- Perform action (in one cycle)
  | Seq [Recipe]                 -- Execute recipes in sequence
  | Par [Recipe]                 -- Fork-join parallelism
  | Wait (Bit 1)                 -- Block until condition holds
  | When (Bit 1) Recipe          -- Conditional recipe
  | If (Bit 1) Recipe Recipe     -- If-then-else recipe
  | While (Bit 1) Recipe         -- Loop
  | Background Recipe            -- Run recipe in background

To illustrate, here is a small state machine that computes the factorial of 10.

fact :: Module ()
fact = do
  -- State
  n   :: Reg (Bit 32) <- makeReg 0
  acc :: Reg (Bit 32) <- makeReg 1

  -- Compute factorial of 10
  let recipe =
        Seq [
          Action do
            n <== 10
        , While (n.val .>. 0) (
            Action do
              n <== n.val - 1
              acc <== acc.val * n.val
          )
        , Action do
            display "fact(10) = " acc.val
            finish
        ]

  runRecipe recipe

Blarney provides a lightweight compiler for the Recipe language (under 100 lines of code), which we invoke above through the call to runRecipe.

A very common use of recipes is to define test sequences. For example, here is a simple test sequence for the Counter module defined earlier.

-- Test-bench for a counter
top :: Module ()
top = do
  -- Instantiate an 4-bit counter
  counter :: Counter 4 <- makeCounter

  -- Sample test sequence
  let test =
        Seq [
          Action do
            counter.inc
        , Action do
            counter.inc
        , Action do
            counter.inc
            counter.dec
        , Action do
            display "counter = " counter.output
            finish
        ]

  runRecipe test

Here, we increment counter on the first cycle, and then again on the second. On the third cycle, we both increment and decrement it in parallel. On the fourth cycle, we display the value and terminate the simulator.

3.9. Statements

For convenience, recipes can also be constucted using do notation. The Stmt monad is simply a wrapper around Recipe, which defines monadic bind as sequential composition. It is entirely syntatic sugar, providing no new functionality.

To illustrate, here’s the factorial example from earlier, rewritten using the Stmt monad.

fact :: Module ()
fact = do
  -- State
  n   :: Reg (Bit 32) <- makeReg 0
  acc :: Reg (Bit 32) <- makeReg 1

  -- Compute factorial of 10
  let stmt = do
        action do
          n <== 10
        while (n.val .>. 0) do
          action do
            n <== n.val - 1
            acc <== acc.val * n.val
        action do
          display "fact(10) = " acc.val
          finish

  runStmt stmt

We have found that some users prefer Recipe syntax, while others prefer Stmt syntax, so we offer both.

3.10. Block RAMs

Blarney provides a variety of block RAM modules commonly supported on FPGAs. They are all based around the following interface.

-- Block RAM interface
-- (Parameterised by the address width a and the data width d)
data RAM a d =
  RAM {
    load    :: a -> Action ()
  , store   :: a -> d -> Action ()
  , out     :: d
  }

When a load is issued for a given address, the value at that address appears on out on the next clock cycle. When a store is issued, the value is written to the RAM on the current cycle, and a load of the new value can be requested on the subsequent cycle. A parallel load and store should only be issued on the same cycle if the RAM has been created as a dual-port RAM (as opposed to a single-port RAM). To illustrate, here is a test bench that creates a single-port block RAM and performs a store followed by a load.

top :: Module ()
top = do
  -- Instantiate a 256 element RAM of 5-bit values
  ram :: RAM (Bit 8) (Bit 5) <- makeRAM

  -- Write 10 to ram[0] and read it back again
  runStmt do
    action do
      store ram 0 10
    action do
      load ram 0
    action do
      display "Got " ram.out
      finish

Somewhat-related to block RAMs are register files. The difference is that a register file allows the value at an address to be determined within a clock cycle. It also allows any number of reads and writes to be performed within the same cycle. Register files have the following interface.

data RegFile a d =
  RegFile {
    index  
                      

鲜花

握手

雷人

路过

鸡蛋
该文章已有0人参与评论

请发表评论

全部评论

专题导读
热门推荐
阅读排行榜

扫描微信二维码

查看手机版网站

随时了解更新最新资讯

139-2527-9053

在线客服(服务时间 9:00~18:00)

在线QQ客服
地址:深圳市南山区西丽大学城创智工业园
电邮:jeky_zhao#qq.com
移动电话:139-2527-9053

Powered by 互联科技 X3.4© 2001-2213 极客世界.|Sitemap