From 0ecfbc43efd67d551e465537db47754005881fbe Mon Sep 17 00:00:00 2001 From: Ryan Slawson Date: Mon, 21 Oct 2024 19:21:05 +0200 Subject: [PATCH] Add unit test for the clock control Wishbone component. --- bittide-instances/bittide-instances.cabal | 1 + .../tests/Tests/ClockControlWb.hs | 408 ++++++++++++++++++ bittide-instances/tests/unittests.hs | 4 +- bittide/src/Bittide/ClockControl/Registers.hs | 1 + firmware-binaries/Cargo.lock | 10 + firmware-binaries/Cargo.toml | 1 + .../clock-control-wb/Cargo.lock.license | 3 + .../test-cases/clock-control-wb/Cargo.toml | 18 + .../test-cases/clock-control-wb/build.rs | 29 ++ .../test-cases/clock-control-wb/memory.x | 18 + .../test-cases/clock-control-wb/src/main.rs | 101 +++++ 11 files changed, 593 insertions(+), 1 deletion(-) create mode 100644 bittide-instances/tests/Tests/ClockControlWb.hs create mode 100644 firmware-binaries/test-cases/clock-control-wb/Cargo.lock.license create mode 100644 firmware-binaries/test-cases/clock-control-wb/Cargo.toml create mode 100644 firmware-binaries/test-cases/clock-control-wb/build.rs create mode 100644 firmware-binaries/test-cases/clock-control-wb/memory.x create mode 100644 firmware-binaries/test-cases/clock-control-wb/src/main.rs diff --git a/bittide-instances/bittide-instances.cabal b/bittide-instances/bittide-instances.cabal index edc32ef12..095d2c1e4 100644 --- a/bittide-instances/bittide-instances.cabal +++ b/bittide-instances/bittide-instances.cabal @@ -184,6 +184,7 @@ test-suite unittests -threaded other-modules: + Tests.ClockControlWb Tests.OverflowResistantDiff Wishbone.Axi Wishbone.DnaPortE2 diff --git a/bittide-instances/tests/Tests/ClockControlWb.hs b/bittide-instances/tests/Tests/ClockControlWb.hs new file mode 100644 index 000000000..c791cd2ba --- /dev/null +++ b/bittide-instances/tests/Tests/ClockControlWb.hs @@ -0,0 +1,408 @@ +-- SPDX-FileCopyrightText: 2023 Google LLC +-- +-- SPDX-License-Identifier: Apache-2.0 +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE OverloadedRecordDot #-} +{-# LANGUAGE RecordWildCards #-} +{-# OPTIONS_GHC -fconstraint-solver-iterations=20 #-} +{-# OPTIONS_GHC -fplugin=Protocols.Plugin #-} + +module Tests.ClockControlWb where + +import Clash.Explicit.Prelude hiding (PeriodToCycles) + +import Clash.Cores.UART (ValidBaud, uart) +import Clash.Cores.UART.Extra +import Clash.Signal (withClockResetEnable) +import Data.Bifunctor (second) +import Data.Char (chr) +import Data.Either (isRight) +import Data.Functor ((<&>)) +import qualified Data.List as L +import Data.Maybe (mapMaybe) +import Language.Haskell.TH +import Project.FilePath +import System.FilePath +import Test.Tasty +import Test.Tasty.HUnit +import Test.Tasty.TH +import Text.Read (readEither) + +import Bittide.Arithmetic.Time (PeriodToCycles) +import Bittide.ClockControl (SpeedChange) +import Bittide.ClockControl.DebugRegister (debugRegisterWb) +import Bittide.ClockControl.Registers (ClockControlData, clockControlWb, clockMod) +import Bittide.DoubleBufferedRam +import Bittide.Instances.Domains +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 + +import Protocols +import VexRiscv + +simBaud :: SNat (MaxBaudRate Basic125) +simBaud = SNat + +sim :: IO () +sim = uartIO @Basic125 stdin stdout simBaud + $ fromSignals + $ \(uartFwd, _) -> (pure (), fst $ dut @Basic125 simBaud clockGen noReset uartFwd) + +case_clock_control_wb_self_test :: Assertion +case_clock_control_wb_self_test = assertBool msg assertion + where + msg = case readCcdResult of + Left m -> "failure:\n" <> m + Right m -> "pass:\n" <> m + assertion = isRight readCcdResult + readUartResult = resultFromUartOutput $ sample uartStream + readCcdResult = readUartResult >>= go + where + go (passStr, numSCs) = + resultFromCcdOutput numSCs (sample ccData) <&> (\rest -> passStr <> "\n" <> rest) + + clk = clockGen @Basic125 + rst = resetGen + ena = enableGen + (uartStream, _, _) = + withClockResetEnable clk rst ena + $ uart simBaud uartTx (pure Nothing) + (uartTx, ccData) = dut simBaud clk rst (pure 0) + +tests :: TestTree +tests = $(testGroupGenerator) + +type Margin = SNat 2 +margin :: Margin +margin = SNat + +type Framesize dom = PeriodToCycles dom (Seconds 1) + +linkMask :: BitVector LinkCount +linkMask = 0b1011011 +linkMaskInt :: Int +linkMaskInt = fromIntegral linkMask +linkMaskPopcnt :: Int +linkMaskPopcnt = fromIntegral $ popCount linkMask + +dut :: + forall dom baud. + (KnownDomain dom, ValidBaud dom baud) => + SNat baud -> + Clock dom -> + Reset dom -> + Signal dom Bit -> + (Signal dom Bit, Signal dom (ClockControlData LinkCount)) +dut baud clk rst usbUartTx = output + where + (_, output) = go ((usbUartTx, pure $ JtagIn low low low), (pure (), pure ())) + + dataCounts :: Vec LinkCount (Signal dom (Signed 27)) + dataCounts = pure <$> iterateI (satSucc SatWrap) 0 + + go = + toSignals + $ withClockResetEnable clk rst enableGen + $ circuit + $ \(uartRx, jtag) -> do + [uartBus, ccWb, dbgWb] <- processingElement @dom peConfig -< jtag + (uartTx, _uartStatus) <- uartWb d256 d16 baud -< (uartBus, uartRx) + [ccd0, ccd1] <- + csDupe + <| clockControlWb + margin + (SNat @(Framesize dom)) + (pure linkMask) + (pure False) + dataCounts + -< ccWb + cm <- cSigMap clockMod -< ccd0 + _dbg <- debugRegisterWb -< (dbgWb, cm) + idC -< (uartTx, ccd1) + + (iMem, dMem) = + $( do + root <- runIO $ findParentContaining "cabal.project" + let + elfDir = root firmwareBinariesDir "riscv32imc-unknown-none-elf" Release + elfPath = elfDir "clock-control-wb" + iSize = 64 * 1024 -- 64 KB + dSize = 64 * 1024 -- 64 KB + memBlobsFromElf BigEndian (Just iSize, Just dSize) elfPath Nothing + ) + + peConfig = + PeConfig + (0b100 :> 0b010 :> 0b001 :> 0b110 :> 0b111 :> Nil) + (Reloadable $ Blob iMem) + (Reloadable $ Blob dMem) + +type UartSample = Maybe (BitVector 8) + +resultFromUartOutput :: [UartSample] -> Either String (String, [Int]) +resultFromUartOutput uartSamples = output + where + linkCount :: Int + linkCount = snatToNum (SNat @LinkCount) + output = + readField "nLinks" linkCount uartSamples + >>= pass1Map2 (readField "linkMask" linkMaskInt) + >>= pass1Map2 (readField "linkMaskPopcnt" linkMaskPopcnt) + >>= pass1Map2 (readField "reframingEnabled" False) + >>= pass1Map2 (readField "linksStable" (0 :: Int)) + >>= pass1Map2 (readField "linksSettled" (0 :: Int)) + >>= pass1Map2 readDataCounts + >>= pass1Map2 readCMods + + pass1Map2 :: + (a -> Either String (String, b)) -> + (String, a) -> + Either String (String, b) + pass1Map2 fn (a, b) = case fn b of + Left f -> Left f + Right (passA, passB) -> Right (a <> "\n" <> passA, passB) + +resultFromCcdOutput :: [Int] -> [ClockControlData LinkCount] -> Either String String +resultFromCcdOutput speedChanges ccdSamples = output2 + where + numSCs = L.length speedChanges + + scList = mapMaybe (.clockMod) ccdSamples + scIntList = L.map getSCInt scList + + output1 = scCheck speedChanges scIntList + output2 = output1 >>= finalCheck + + scCheck :: [Int] -> [Int] -> Either String [Int] + scCheck l1 l2 = case (l1, l2) of + (_, []) -> undefined + ([], rest) -> Right rest + (h1 : t1, h2 : t2) -> next + where + next = + if h1 == h2 + then scCheck t1 t2 + else + Left + $ "UART sample says `" + <> show h1 + <> "`, but CcWb says `" + <> show h2 + <> "`" + + finalCheck :: [Int] -> Either String String + finalCheck = finalCheck' linkMaskPopcnt + where + finalCheck' 0 _ = + Right $ "clockMod: successfully read " <> show numSCs <> "speed changes" + finalCheck' n [] = + Left + $ "reached end of stream while trying to read clock change padding. remaining: " + <> show (n - 1) + finalCheck' n (h : t) = + if h == 0 + then finalCheck' (n - 1) t + else + Left + $ "failed to read clock change padding. expected `0`, found `" + <> show h + <> "`" + +readDataCounts :: [UartSample] -> Either String (String, [UartSample]) +readDataCounts smpls = output5 + where + linkCount :: Int + linkCount = snatToNum (SNat @LinkCount) + + output1 = readFieldName "dataCounts" smpls + output2 = output1 <&> dropNUart 3 -- skip ` [(` after colon + output3 = output2 >>= readDataCountsList linkCount + output4 = output3 <&> dropNUart 3 -- skip `)]\n` at end of list + output5 = output4 <&> ("dataCounts: successfully read " <> show linkCount <> "data counts",) + + readDataCountsList :: Int -> [UartSample] -> Either String [UartSample] + readDataCountsList 0 rest = Right rest + readDataCountsList n [] = + Left + $ "reached end of stream while trying to read data counts list with " + <> show (n - 1) + <> " counts remaining to read" + readDataCountsList n list = readTuple n list >>= readDataCountsList (n - 1) + + readTuple :: Int -> [UartSample] -> Either String [UartSample] + readTuple n list = output4' + where + output1' = readTupleVal True list + output2' = output1' <&> dropNUart 2 -- skip `, ` after first number + output3' = output2' >>= readTupleVal False + output4' = output3' <&> if n > 1 then dropNUart 4 else id -- skip `), (` after second number + curIndex = linkCount - n + maskBit = bitToBool (bv2v linkMask !! curIndex) + + readTupleVal True [] = + Left + $ "found end of stream while looking for " + <> show curIndex + <> " as element 0 of tuple at index " + <> show curIndex + readTupleVal False [] = + Left + $ "found end of stream while looking for " + <> show checkVal + <> " as element 0 of tuple at index " + <> show curIndex + where + checkVal = if maskBit then curIndex else 0 + readTupleVal firstElem (Nothing : t) = readTupleVal firstElem t + readTupleVal firstElem ((Just val) : t) = + if cmpResult + then Right t + else + Left + $ "expected value `" + <> show checkVal + <> "` as tuple element " + <> show tupleElem + <> " at index " + <> show curIndex + <> " of dataCounts, found `" + <> show char + <> "` instead" + where + tupleElem = if firstElem then 1 :: Int else 0 + valNum = fromIntegral val - fromEnum '0' + char = chr valNum + checkVal = if maskBit then curIndex else 0 + cmpVal = if firstElem then curIndex else checkVal + cmpResult = valNum == cmpVal + +dropNUart :: Int -> [UartSample] -> [UartSample] +dropNUart 0 list = list +dropNUart _ [] = [] +dropNUart n (Nothing : t) = dropNUart n t +dropNUart n ((Just _) : t) = dropNUart (n - 1) t + +readCMods :: [UartSample] -> Either String (String, [Int]) +readCMods smpls = output5 + where + output1 = readFieldName "clockMod" smpls + output2 = output1 >>= readNumCMods "" + output3 = output2 <&> second (dropNUart 3) + output5 = output3 >>= readCModsList + + readNumCMods :: String -> [UartSample] -> Either String (Int, [UartSample]) + readNumCMods readIn [] = + Left + $ "failed to read number of clockMods - found end of stream. read: `" + <> readIn + <> "`" + readNumCMods readIn (maybeNewChar : t) + | mnc == Just ')' = readEither readIn <&> (,t) + | otherwise = readNumCMods readIn' t + where + mnc :: Maybe Char + mnc = chr . fromIntegral <$> maybeNewChar + readIn' = maybeAppendFromUart readIn maybeNewChar + + readCModsList :: (Int, [UartSample]) -> Either String (String, [Int]) + readCModsList (nMods, samples) = readCModsList' nMods samples + where + readCModsList' 0 _ = Right ("clockMods: successfully read " <> show nMods <> " clockMods", []) + readCModsList' n [] = + Left + $ "failed to read clockMods. read " + <> show (nMods - n - 1) + <> " before reaching end of stream" + readCModsList' n (Nothing : t) = readCModsList' n t + readCModsList' n ((Just val) : t) = output + where + sc :: Int + sc = fromIntegral val - fromEnum '0' + valChar :: Char + valChar = chr $ fromIntegral val + output = + if 0 <= sc && sc <= 2 + then joinedWithNext + else + Left + $ "read invalid speed change `" + <> show valChar + <> "` at index " + <> show (nMods - n - 1) + <> ". must be 0, 1, or 2" + next = readCModsList' (n - 1) (dropNUart 2 t) + joinedWithNext = case next of + Right (passed, list) -> Right (passed, sc : list) + Left failed -> Left failed + +getSCInt :: SpeedChange -> Int +getSCInt = fromIntegral . pack + +readField :: + (Eq a, Read a, Show a) => + String -> + a -> + [UartSample] -> + Either String (String, [UartSample]) +readField fieldName expectedVal samples = output4 + where + output1 = readFieldName fieldName samples + output2 = output1 <&> dropNUart 1 -- skip ` ` after colon + output3 = output2 >>= readVal "" + output4 = output3 <&> (successStr,) + + showEv = show expectedVal + successStr = fieldName <> ": " <> showEv + + readVal :: String -> [UartSample] -> Either String [UartSample] + readVal rv [] = + Left + $ "failed to read value - found end of stream. expected `" + <> showEv + <> "`, found \"" + <> rv + <> "\"" + readVal rv (maybeNewChar : t) + | maybeNewChar' == Just '\n' = + if read rv == expectedVal + then Right t + else + Left + $ "received end of line while trying to read value for field `" + <> fieldName + <> "`. read: `" + <> rv + <> "`" + | otherwise = readVal rv' t + where + rv' = maybeAppendFromUart rv maybeNewChar + maybeNewChar' = chr . fromIntegral <$> maybeNewChar + +readFieldName :: String -> [UartSample] -> Either String [UartSample] +readFieldName name = readFieldName' [] + where + readFieldName' readIn [] = + Left + $ "found end of stream while attempting to read field name `" + <> name + <> "`. read: `" + <> readIn + <> "`" + readFieldName' readIn (maybeChar : t) + | mChar' == Just ':' = Right t + | mChar' == Just '(' = Right t + | otherwise = readFieldName' readIn' t + where + mChar' = chr . fromIntegral <$> maybeChar + readIn' = maybeAppendFromUart readIn maybeChar + +maybeAppendFromUart :: String -> Maybe (BitVector 8) -> String +maybeAppendFromUart str mChar = case mChar' of + Just c -> str <> [c] + Nothing -> str + where + mChar' = chr . fromIntegral <$> mChar diff --git a/bittide-instances/tests/unittests.hs b/bittide-instances/tests/unittests.hs index 3ea3eedc3..bceaa8565 100644 --- a/bittide-instances/tests/unittests.hs +++ b/bittide-instances/tests/unittests.hs @@ -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.DnaPortE2 as DnaPortE2 @@ -17,7 +18,8 @@ tests :: TestTree tests = testGroup "Unittests" - [ DnaPortE2.tests + [ ClockControlWb.tests + , DnaPortE2.tests , Ord.tests , Time.tests , Axi.tests diff --git a/bittide/src/Bittide/ClockControl/Registers.hs b/bittide/src/Bittide/ClockControl/Registers.hs index a04cb06d1..726d281a9 100644 --- a/bittide/src/Bittide/ClockControl/Registers.hs +++ b/bittide/src/Bittide/ClockControl/Registers.hs @@ -24,6 +24,7 @@ data ClockControlData (nLinks :: Nat) = ClockControlData , allStable :: Bool , allSettled :: Bool } + deriving (Generic, NFDataX) instance HasField diff --git a/firmware-binaries/Cargo.lock b/firmware-binaries/Cargo.lock index a56054afa..c286a1957 100644 --- a/firmware-binaries/Cargo.lock +++ b/firmware-binaries/Cargo.lock @@ -88,6 +88,16 @@ dependencies = [ "ufmt", ] +[[package]] +name = "clock-control-wb" +version = "0.1.0" +dependencies = [ + "bittide-sys", + "rand", + "riscv-rt", + "ufmt", +] + [[package]] name = "critical-section" version = "1.1.1" diff --git a/firmware-binaries/Cargo.toml b/firmware-binaries/Cargo.toml index 8dd32695f..89dc80ae0 100644 --- a/firmware-binaries/Cargo.toml +++ b/firmware-binaries/Cargo.toml @@ -16,6 +16,7 @@ members = [ "examples/hello", "examples/smoltcp_echo", + "test-cases/clock-control-wb", "test-cases/dna_port_e2_test", "test-cases/time_self_test", "test-cases/axi_stream_self_test", diff --git a/firmware-binaries/test-cases/clock-control-wb/Cargo.lock.license b/firmware-binaries/test-cases/clock-control-wb/Cargo.lock.license new file mode 100644 index 000000000..848612f0e --- /dev/null +++ b/firmware-binaries/test-cases/clock-control-wb/Cargo.lock.license @@ -0,0 +1,3 @@ +SPDX-FileCopyrightText: 2022 Google LLC + +SPDX-License-Identifier: CC0-1.0 diff --git a/firmware-binaries/test-cases/clock-control-wb/Cargo.toml b/firmware-binaries/test-cases/clock-control-wb/Cargo.toml new file mode 100644 index 000000000..d4b2f53a8 --- /dev/null +++ b/firmware-binaries/test-cases/clock-control-wb/Cargo.toml @@ -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" diff --git a/firmware-binaries/test-cases/clock-control-wb/build.rs b/firmware-binaries/test-cases/clock-control-wb/build.rs new file mode 100644 index 000000000..503fd91f0 --- /dev/null +++ b/firmware-binaries/test-cases/clock-control-wb/build.rs @@ -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"); +} diff --git a/firmware-binaries/test-cases/clock-control-wb/memory.x b/firmware-binaries/test-cases/clock-control-wb/memory.x new file mode 100644 index 000000000..5c6f8a19c --- /dev/null +++ b/firmware-binaries/test-cases/clock-control-wb/memory.x @@ -0,0 +1,18 @@ +/* +SPDX-FileCopyrightText: 2022 Google LLC + +SPDX-License-Identifier: CC0-1.0 +*/ + +MEMORY +{ + IMEM : ORIGIN = 0x80000000, LENGTH = 64K + DMEM : ORIGIN = 0x40000000, LENGTH = 64K +} + +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); diff --git a/firmware-binaries/test-cases/clock-control-wb/src/main.rs b/firmware-binaries/test-cases/clock-control-wb/src/main.rs new file mode 100644 index 000000000..0b3d5ca88 --- /dev/null +++ b/firmware-binaries/test-cases/clock-control-wb/src/main.rs @@ -0,0 +1,101 @@ +#![no_std] +#![cfg_attr(not(test), no_main)] + +// SPDX-FileCopyrightText: 2022 Google LLC +// +// SPDX-License-Identifier: Apache-2.0 + +use core::panic::PanicInfo; + +use bittide_sys::{ + clock_control::{ClockControl, SpeedChange}, + uart::Uart, +}; +use core::fmt::Write; +use rand::{distributions::Uniform, rngs::SmallRng, Rng, SeedableRng}; + +#[cfg(not(test))] +use riscv_rt::entry; + +const RNG_SEED: [u8; 16] = { + let rng_seed = core::env!("RNG_SEED").as_bytes(); + let mut out = [0; 16]; + + let mut i = 0; + while i < rng_seed.len() && (i / 8) < 16 { + let byte = i / 8; + let shift = i % 8; + let val = rng_seed[i]; + i += 1; + let val = match val { + b'0' => 0, + b'1' => 1, + _ => continue, + }; + out[byte] |= val << shift; + } + out +}; + +#[cfg_attr(not(test), entry)] +#[allow(clippy::empty_loop)] +fn main() -> ! { + #[allow(clippy::zero_ptr)] // we might want to change the address! + let mut uart = unsafe { Uart::new(0x2000_0000 as *const ()) }; + let mut cc = unsafe { ClockControl::from_base_addr(0xC000_0000 as *const u32) }; + + writeln!(uart, "nLinks: {}", cc.num_links()).unwrap(); + writeln!(uart, "linkMask: {}", cc.link_mask()).unwrap(); + writeln!(uart, "linkMaskPopcnt: {}", cc.up_links()).unwrap(); + writeln!( + uart, + "reframingEnabled: {}", + if cc.reframing_enabled() { + "True" + } else { + "False" + } + ) + .unwrap(); + writeln!(uart, "linksStable: {}", cc.links_stable()).unwrap(); + writeln!(uart, "linksSettled: {}", cc.links_settled()).unwrap(); + + write!(uart, "dataCounts: [").unwrap(); + cc.data_counts().enumerate().for_each(|(i, dc)| { + let sep = if i + 1 < cc.num_links() as usize { + ", " + } else { + "" + }; + write!(uart, "({i}, {dc}){sep}").unwrap(); + }); + writeln!(uart, "]").unwrap(); + + let mut rng = SmallRng::from_seed(RNG_SEED); + let amt = rng.gen_range(16..=128); + write!(uart, "clockMod({amt}): [").unwrap(); + rng.sample_iter(Uniform::new_inclusive(0, 2)) + .take(amt) + .map(|val| unsafe { core::mem::transmute::(val) }) + .enumerate() + .for_each(|(i, sc)| { + let sep = if i + 1 < amt { ", " } else { "" }; + cc.change_speed(sc); + write!(uart, "{}{sep}", sc as u8).unwrap(); + }); + writeln!(uart, "]").unwrap(); + + // Mark end of transmission - should hopefully be unique enough? + for _ in 0..cc.up_links() { + cc.change_speed(SpeedChange::NoChange); + } + + loop {} +} + +#[panic_handler] +fn panic_handler(_info: &PanicInfo) -> ! { + loop { + continue; + } +}