Skip to content

Commit

Permalink
Add echo test for the HAL of scatter and gather unit
Browse files Browse the repository at this point in the history
  • Loading branch information
hiddemoll committed Dec 13, 2024
1 parent a79c3da commit a828bcb
Show file tree
Hide file tree
Showing 9 changed files with 251 additions and 1 deletion.
1 change: 1 addition & 0 deletions bittide-instances/bittide-instances.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,7 @@ test-suite unittests
Wishbone.Axi
Wishbone.CaptureUgn
Wishbone.DnaPortE2
Wishbone.ScatterGather
Wishbone.Time

build-depends:
Expand Down
106 changes: 106 additions & 0 deletions bittide-instances/tests/Wishbone/ScatterGather.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,106 @@
-- SPDX-FileCopyrightText: 2024 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE NumericUnderscores #-}
{-# OPTIONS_GHC -fplugin=Protocols.Plugin #-}

module Wishbone.ScatterGather where

import Clash.Explicit.Prelude
import Clash.Prelude (HiddenClockResetEnable, withClockResetEnable)

import Data.Char (chr)
import Data.Maybe (mapMaybe)
import Language.Haskell.TH
import Project.FilePath
import Protocols
import Protocols.Idle
import System.FilePath
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import VexRiscv (DumpVcd (NoDumpVcd))

import Bittide.Calendar
import Bittide.DoubleBufferedRam
import Bittide.ProcessingElement
import Bittide.ProcessingElement.Util
import Bittide.ScatterGather
import Bittide.SharedTypes
import Bittide.Wishbone

import qualified Protocols.Df as Df
import qualified Prelude as P

case_scatter_gather_echo_test :: Assertion
case_scatter_gather_echo_test = do
assertBool
msg
(P.head (lines simResult) == "Written data was read back correctly")
where
msg = "Received the following from the CPU over UART:\n" <> simResult
simResult = chr . fromIntegral <$> mapMaybe Df.dataToMaybe uartStream

uartStream =
sampleC def{timeoutAfter = 100_000}
$ withClockResetEnable clockGen resetGen enableGen
$ dut @System @4 @32 scatterConfig gatherConfig

scatterConfig = ScatterConfig $ CalendarConfig (SNat @32) scatterCal scatterCal
gatherConfig = GatherConfig $ CalendarConfig (SNat @32) gatherCal gatherCal

-- Padding is required to increase the duration of a metacycle, giving the CPU
-- enough time to write to the gather memory and read from the scatter memory.
-- The calendar for the scatter unit is delayed by one cycle.
padding = 256
incrementingCal = genIncrementingCalendar @16
gatherCal = incrementingCal :< ValidEntry maxBound (padding - 1 :: Unsigned 16)
scatterCal = (ValidEntry 0 0 :> incrementingCal) :< ValidEntry maxBound (padding - 2)

genIncrementingCalendar ::
forall size repititionBits.
(KnownNat size, KnownNat repititionBits) =>
Calendar size (Index size) repititionBits
genIncrementingCalendar = iterateI f (ValidEntry 0 0)
where
f (ValidEntry i _) = ValidEntry (succ i) 0

{- | A simulation-only instance containing just VexRisc with UART and a scatter and a
gather unit. The VexRiscv runs the `scatter_gather_test` binary from `firmware-binaries`.
-}
dut ::
forall dom nBytes addrW.
( HiddenClockResetEnable dom
, KnownNat nBytes
, 1 <= nBytes
, KnownNat addrW
) =>
ScatterConfig nBytes addrW ->
GatherConfig nBytes addrW ->
Circuit () (Df dom (BitVector 8))
dut scatterConfig gatherConfig = circuit $ do
(uartRx, jtagIdle, wbGuCal, wbSuCal) <- idleSource -< ()
[uartBus, wbSu, wbGu] <- processingElement NoDumpVcd peConfig -< jtagIdle
(uartTx, _uartStatus) <- uartInterfaceWb d16 d2 uartSim -< (uartBus, uartRx)
link <- gatherUnitWbC gatherConfig -< (wbGu, wbGuCal)
scatterUnitWbC scatterConfig -< (link, wbSu, wbSuCal)
idC -< uartTx
where
(iMem, dMem) =
$( do
root <- runIO $ findParentContaining "cabal.project"
let
elfDir = root </> firmwareBinariesDir "riscv32imc-unknown-none-elf" Release
elfPath = elfDir </> "scatter_gather_test"

memBlobsFromElf BigEndian (Nothing, Nothing) elfPath Nothing
)

peConfig =
PeConfig
(0b000 :> 0b001 :> 0b010 :> 0b011 :> 0b100 :> Nil)
(Reloadable $ Blob iMem)
(Reloadable $ Blob dMem)

tests :: TestTree
tests = $(testGroupGenerator)
2 changes: 2 additions & 0 deletions bittide-instances/tests/unittests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import qualified Tests.OverflowResistantDiff as Ord
import qualified Wishbone.Axi as Axi
import qualified Wishbone.CaptureUgn as CaptureUgn
import qualified Wishbone.DnaPortE2 as DnaPortE2
import qualified Wishbone.ScatterGather as ScatterGather
import qualified Wishbone.Time as Time

tests :: TestTree
Expand All @@ -21,6 +22,7 @@ tests =
"Unittests"
[ CaptureUgn.tests
, ClockControlWb.tests
, ScatterGather.tests
, DnaPortE2.tests
, Ord.tests
, Time.tests
Expand Down
9 changes: 9 additions & 0 deletions firmware-binaries/Cargo.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 2 additions & 1 deletion firmware-binaries/Cargo.toml
Original file line number Diff line number Diff line change
Expand Up @@ -16,11 +16,12 @@ members = [
"examples/hello",
"examples/smoltcp_client",

"test-cases/axi_stream_self_test",
"test-cases/capture_ugn_test",
"test-cases/clock-control-wb",
"test-cases/dna_port_e2_test",
"test-cases/scatter_gather_test",
"test-cases/time_self_test",
"test-cases/axi_stream_self_test",

"clock-control-reg-cpy",
"clock-control",
Expand Down
17 changes: 17 additions & 0 deletions firmware-binaries/test-cases/scatter_gather_test/Cargo.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
# SPDX-FileCopyrightText: 2024 Google LLC
#
# SPDX-License-Identifier: CC0-1.0

[package]
name = "scatter_gather_test"
version = "0.1.0"
edition = "2021"
license = "Apache-2.0"
authors = ["Google LLC"]

# See more keys and their definitions at https://doc.rust-lang.org/cargo/reference/manifest.html

[dependencies]
riscv-rt = "0.11.0"
bittide-sys = { path = "../../../firmware-support/bittide-sys" }
ufmt = "0.2.0"
23 changes: 23 additions & 0 deletions firmware-binaries/test-cases/scatter_gather_test/build.rs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
// SPDX-FileCopyrightText: 2024 Google LLC
//
// SPDX-License-Identifier: Apache-2.0

use std::env;
use std::fs;
use std::path::Path;

/// Put the linker script somewhere the linker can find it.
fn main() {
let out_dir = env::var("OUT_DIR").expect("No out dir");
let dest_path = Path::new(&out_dir).join("memory.x");
fs::write(dest_path, include_bytes!("memory.x")).expect("Could not write file");

if env::var("CARGO_CFG_TARGET_ARCH").unwrap() == "riscv32" {
println!("cargo:rustc-link-arg=-Tmemory.x");
println!("cargo:rustc-link-arg=-Tlink.x"); // linker script from riscv-rt
}
println!("cargo:rustc-link-search={out_dir}");

println!("cargo:rerun-if-changed=memory.x");
println!("cargo:rerun-if-changed=build.rs");
}
18 changes: 18 additions & 0 deletions firmware-binaries/test-cases/scatter_gather_test/memory.x
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
/*
SPDX-FileCopyrightText: 2024 Google LLC
SPDX-License-Identifier: CC0-1.0
*/

MEMORY
{
IMEM : ORIGIN = 0x80000000, LENGTH = 64K
DMEM : ORIGIN = 0x20000000, LENGTH = 32K
}

REGION_ALIAS("REGION_TEXT", IMEM);
REGION_ALIAS("REGION_RODATA", DMEM);
REGION_ALIAS("REGION_DATA", DMEM);
REGION_ALIAS("REGION_BSS", DMEM);
REGION_ALIAS("REGION_HEAP", DMEM);
REGION_ALIAS("REGION_STACK", DMEM);
73 changes: 73 additions & 0 deletions firmware-binaries/test-cases/scatter_gather_test/src/main.rs
Original file line number Diff line number Diff line change
@@ -0,0 +1,73 @@
// SPDX-FileCopyrightText: 2024 Google LLC
//
// SPDX-License-Identifier: Apache-2.0
#![no_std]
#![cfg_attr(not(test), no_main)]

use bittide_sys::gather_unit::GatherUnit;
use bittide_sys::scatter_unit::ScatterUnit;
use bittide_sys::uart::Uart;
use core::fmt::Write;
#[cfg(not(test))]
use riscv_rt::entry;

const UART_ADDR: *const () = (0b010 << 29) as *const ();
const SCATTER_ADDR: *const () = (0b011 << 29) as *const ();
const GATHER_ADDR: *const () = (0b100 << 29) as *const ();

// Therefore, `MEM_SIZE` is twice as large as the calendar size. `MEM_SIZE` is
// defined as 32-bit words. For this test a calendar depth of 16 64-bit words is used.
const MEM_SIZE: usize = 2 * 16;

#[cfg_attr(not(test), entry)]
fn main() -> ! {
// Initialize peripherals.
let mut uart = unsafe { Uart::new(UART_ADDR) };
let scatter_unit: ScatterUnit<MEM_SIZE> = unsafe { ScatterUnit::new(SCATTER_ADDR) };
let gather_unit: GatherUnit<MEM_SIZE> = unsafe { GatherUnit::new(GATHER_ADDR) };

// For this test an array of incrementing values is written to the full gather
// memory. The calendars for the scatter and gather units are expected to write the
// data sent over the link to the same memory location in the scatter unit. This makes
// this test behave like an 'echo'.
// Test takes 3 metacycles:
// 1: CPU writes to the gather unit memory
// 2: Gather memory is written over the link to the scatter memory
// 3: Read from scatter memory

// First metacycle
let source: [u8; MEM_SIZE] = core::array::from_fn(|i| i as u8);
gather_unit.wait_for_new_metacycle();
unsafe { gather_unit.copy_from_slice(&source, 0) };

// Second metacycle
gather_unit.wait_for_new_metacycle();

// Third metacycle
gather_unit.wait_for_new_metacycle();
let mut destination: [u8; MEM_SIZE] = [0; MEM_SIZE];
unsafe { scatter_unit.copy_to_slice(destination.as_mut(), 0) };

// Check if slices are equal
if source == destination {
writeln!(uart, "Written data was read back correctly").unwrap();
} else {
writeln!(uart, "Could not read back written data").unwrap();
writeln!(uart, "Written to gather memory:").unwrap();
writeln!(uart, "{:?}", source).unwrap();
writeln!(uart, "Read from scatter memory:").unwrap();
writeln!(uart, "{:?}", destination).unwrap();
}
loop {
continue;
}
}

#[panic_handler]
fn panic_handler(info: &core::panic::PanicInfo) -> ! {
let mut uart = unsafe { Uart::new(UART_ADDR) };
writeln!(uart, "Panicked! #{info}").unwrap();
loop {
continue;
}
}

0 comments on commit a828bcb

Please sign in to comment.