Skip to content

Commit

Permalink
Add unit test for the clock control Wishbone component.
Browse files Browse the repository at this point in the history
`clock-control-wb` suggestions

Simplify `Tests.ClockControlWb`

Fixed expected data counts.

Formatting fixes.
  • Loading branch information
rslawson committed Nov 4, 2024
1 parent 81e0727 commit 49327a5
Show file tree
Hide file tree
Showing 12 changed files with 413 additions and 2 deletions.
1 change: 1 addition & 0 deletions bittide-instances/bittide-instances.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -191,6 +191,7 @@ test-suite unittests
-threaded

other-modules:
Tests.ClockControlWb
Tests.OverflowResistantDiff
Wishbone.Axi
Wishbone.CaptureUgn
Expand Down
226 changes: 226 additions & 0 deletions bittide-instances/tests/Tests/ClockControlWb.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,226 @@
-- SPDX-FileCopyrightText: 2023 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=20 #-}
{-# OPTIONS_GHC -fplugin=Protocols.Plugin #-}

module Tests.ClockControlWb where

-- preludes
import Clash.Explicit.Prelude hiding (PeriodToCycles, many)

-- external imports
import Clash.Signal (withClockResetEnable)
import Data.Char (chr)
import Data.Maybe (mapMaybe)
import Data.String.Interpolate
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 Text.Parsec
import Text.Parsec.String

-- internal imports
import Bittide.Arithmetic.Time (PeriodToCycles)
import Bittide.ClockControl.DebugRegister (DebugRegisterCfg (..), debugRegisterWb)
import Bittide.ClockControl.Registers (ClockControlData, clockControlWb, clockMod)
import Bittide.DoubleBufferedRam
import Bittide.Instances.Hitl.HwCcTopologies (cSigMap, csDupe)
import Bittide.Instances.Hitl.Setup (LinkCount)
import Bittide.ProcessingElement
import Bittide.ProcessingElement.Util
import Bittide.SharedTypes
import Bittide.Wishbone

-- qualified imports
import qualified Data.List as L
import qualified Protocols.Df as Df

-- | The expected output of the UART
data SerialResult = SerialResult
{ linkCount :: Int
, linkMask :: Int
, linkMaskPopcnt :: Int
, reframingEnabled :: Bool
, linksStable :: Int
, linksSettled :: Int
, dataCounts :: [(Int, Int)]
, clockMod :: [Int]
}
deriving (Show, Eq)

-- | Simulate the serial output of the cpu
sim :: IO ()
sim =
putStr
$ fmap (chr . fromIntegral)
. mapMaybe Df.dataToMaybe
$ fst (sampleC def dut)

case_clock_control_wb_self_test :: Assertion
case_clock_control_wb_self_test = do
case parse resultParser "" uartString of
Left err -> do
print err
assertFailure "Could not parse output"
Right actual -> do
let
expected =
SerialResult
{ linkCount = linkCount
, linkMask = fromIntegral linkMask
, linkMaskPopcnt = linkMaskPopcnt
, reframingEnabled = False
, linksStable = 0
, linksSettled = 0
, dataCounts = expectedDataCounts
, clockMod =
L.take (L.length actual.clockMod) $ fromIntegral . pack <$> mapMaybe clockMod ccData
}
putStrLn ""
putStrLn "Actual |"
print actual
print expected
putStrLn "Expected ^"
assertBool "Expected and actual differ" $ actual == expected
where
uartString = chr . fromIntegral <$> mapMaybe Df.dataToMaybe uartStream
(uartStream, ccData) = sampleC def dut

type Margin = SNat 2
type Framesize = PeriodToCycles System (Seconds 1)

margin :: Margin
margin = SNat
framesize :: SNat Framesize
framesize = SNat
linkCount :: Int
linkCount = snatToNum (SNat @LinkCount)
linkMask :: BitVector LinkCount
linkMask = 0b1011011
linkMaskPopcnt :: Int
linkMaskPopcnt = fromIntegral $ popCount linkMask

dataCounts :: Vec LinkCount (Signed 27)
dataCounts = iterateI (satSucc SatWrap) 0

expectedDataCounts :: [(Int, Int)]
expectedDataCounts = L.zip [0 ..] $ toList $ applyMask linkMask dataCounts
where
applyMask m = zipWith go (bitCoerce m)
go m v = if m then fromIntegral v else 0

debugRegisterConfig :: DebugRegisterCfg
debugRegisterConfig =
DebugRegisterCfg
{ reframingEnabled = False
}

dut ::
Circuit () (Df System (BitVector 8), CSignal System (ClockControlData LinkCount))
dut =
withClockResetEnable
clockGen
resetGen
enableGen
$ circuit
$ \_unit -> do
(uartRx, jtag) <- idleSource -< ()
[uartBus, ccWb, dbgWb] <- processingElement peConfig -< jtag
(uartTx, _uartStatus) <- uartInterfaceWb d2 d2 uartSim -< (uartBus, uartRx)
[ccd0, ccd1] <-
csDupe
<| clockControlWb
margin
framesize
(pure linkMask)
(pure <$> dataCounts)
-< ccWb
cm <- cSigMap clockMod -< ccd0
_dbg <- debugRegisterWb (pure debugRegisterConfig) -< (dbgWb, cm)
idC -< (uartTx, ccd1)
where
(iMem, dMem) =
$( do
root <- runIO $ findParentContaining "cabal.project"
let
elfDir = root </> firmwareBinariesDir "riscv32imc-unknown-none-elf" Release
elfPath = elfDir </> "clock-control-wb"
iSize = 8 * 1024 -- 16 KB
dSize = 64 * 1024 -- 256 KB
memBlobsFromElf BigEndian (Just iSize, Just dSize) elfPath Nothing
)

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

-- | Parse the output of the UART
resultParser :: Parser SerialResult
resultParser = do
linkCountResult <- expectField "nLinks"
linkMaskResult <- expectField "linkMask"
linkMaskPopcntResult <- expectField "linkMaskPopcnt"
reframingEnabledResult <- expectField "reframingEnabled"
linksStableResult <- expectField "linksStable"
linksSettledResult <- expectField "linksSettled"
dataCountsResult <- expectField "dataCounts"
clockModResult <- expectField "clockMod"
return
SerialResult
{ linkCount = linkCountResult
, linkMask = linkMaskResult
, linkMaskPopcnt = linkMaskPopcntResult
, reframingEnabled = reframingEnabledResult
, linksStable = linksStableResult
, linksSettled = linksSettledResult
, dataCounts = dataCountsResult
, clockMod = clockModResult
}

{- | A parser that parses a string in the form "name: value\n"
The parsed name should be equal to the given fieldName
-}
expectField :: (Read a) => String -> Parser a
expectField fieldName = do
(actualName, value) <- fieldParser
if actualName == fieldName
then pure value
else do
parserFail
[__i|
expectField failed to match the expected field name.
Expected field: #{fieldName}
Actual field: #{actualName}|]

-- | Parse a field of the form "name: value\n"
fieldParser :: (Read a) => Parser (String, a)
fieldParser = do
name <- manyTill anyChar (try (string ": "))
value <- manyTill anyChar (try (string "\n"))
return (name, read value)

{- | Return the beginning of a list until you detect a certain sublist
That substring is not included in the result.
-}
splitAtSublist :: (Eq a) => [a] -> [a] -> Maybe ([a], [a])
splitAtSublist subList = recurse []
where
recurse _ [] = Nothing
recurse acc remaining@(h : t)
| subList `L.isPrefixOf` remaining = Just (acc, L.drop (L.length subList) remaining)
| otherwise = recurse (acc <> [h]) t

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 @@ -8,6 +8,7 @@ import Prelude

import Test.Tasty

import qualified Tests.ClockControlWb as ClockControlWb
import qualified Tests.OverflowResistantDiff as Ord
import qualified Wishbone.Axi as Axi
import qualified Wishbone.CaptureUgn as CaptureUgn
Expand All @@ -19,6 +20,7 @@ tests =
testGroup
"Unittests"
[ CaptureUgn.tests
, ClockControlWb.tests
, DnaPortE2.tests
, Ord.tests
, Time.tests
Expand Down
2 changes: 1 addition & 1 deletion bittide/src/Bittide/ClockControl/Registers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ data ClockControlData (nLinks :: Nat) = ClockControlData
, allStable :: Bool
, allSettled :: Bool
}
deriving (Generic, NFDataX)
deriving (Generic, NFDataX, ShowX, Show)

deriveSignalHasFields ''ClockControlData

Expand Down
2 changes: 1 addition & 1 deletion bittide/src/Bittide/ClockControl/StabilityChecker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ data StabilityIndication = StabilityIndication
-- ^ Indicates whether the signal is stable and close to
-- 'targetDataCount'.
}
deriving (Generic, NFDataX, BitPack)
deriving (Generic, NFDataX, BitPack, ShowX, Show)

deriveSignalHasFields ''StabilityIndication

Expand Down
10 changes: 10 additions & 0 deletions firmware-binaries/Cargo.lock

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

1 change: 1 addition & 0 deletions firmware-binaries/Cargo.toml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ members = [
"examples/smoltcp_client",

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

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

18 changes: 18 additions & 0 deletions firmware-binaries/test-cases/clock-control-wb/Cargo.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
# SPDX-FileCopyrightText: 2022 Google LLC
#
# SPDX-License-Identifier: CC0-1.0

[package]
name = "clock-control-wb"
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]
bittide-sys = { path = "../../../firmware-support/bittide-sys" }
rand = {version = "0.8.3", features = ["small_rng"], default-features = false }
riscv-rt = "0.11.0"
ufmt = "0.2.0"
29 changes: 29 additions & 0 deletions firmware-binaries/test-cases/clock-control-wb/build.rs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
// SPDX-FileCopyrightText: 2022 Google LLC
//
// SPDX-License-Identifier: Apache-2.0

use std::env;
use std::fs;
use std::path::Path;
use std::time::SystemTime;
use std::time::UNIX_EPOCH;

/// 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}");

let now = SystemTime::now();
let rng_seed = now.duration_since(UNIX_EPOCH).unwrap().as_millis();
println!("cargo:rustc-env=RNG_SEED='{rng_seed:0128b}'");

println!("cargo:rerun-if-changed=memory.x");
println!("cargo:rerun-if-changed=build.rs");
}
18 changes: 18 additions & 0 deletions firmware-binaries/test-cases/clock-control-wb/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 = 0x40000000, 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);
Loading

0 comments on commit 49327a5

Please sign in to comment.