Skip to content

Commit

Permalink
Refactor to allow disabling clock offsets
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Aug 19, 2024
1 parent 5486c6c commit 0de395a
Show file tree
Hide file tree
Showing 9 changed files with 75 additions and 67 deletions.
2 changes: 1 addition & 1 deletion .github/simulation/staging.json
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
[
{"topology": "complete", "hmem": 16, "steps": 1000000, "args": "--nodes 2 --clock-offsets [-2,2] --frame-size 1500"}
{"topology": "complete", "hmem": 16, "steps": 1000000, "args": "--nodes 2 --clock-offsets 'Just [-2,2]' --frame-size 1500"}
]
12 changes: 6 additions & 6 deletions bittide-experiments/src/Bittide/Report/ClockControl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -267,13 +267,9 @@ toLatex refDom datetime runref header clocksPdf ebsPdf topTikz ids SimConf{..} =
, " stability detector - margin:"
, " & \\textpm\\," <> formatThousands stabilityMargin <> " elements \\\\"
, " when stable, stop after:"
, " & " <> maybe "not used" qtyMs stopAfterStableMs <> " \\\\"
, " & " <> maybe "\\textit{not used}" qtyMs stopAfterStableMs <> " \\\\"
, " clock offsets:"
, " & "
<> intercalate
"; "
(qtyPpm . roundDoubleInteger . fsToPpm refDom . floatToDouble <$> clockOffsets)
<> " \\\\"
, " & " <> maybe "\\textit{not used}" formatOffsets clockOffsets <> " \\\\"
, " startup delays:"
, " & " <> intercalate "; " (qtyMs <$> startupDelaysMs) <> " \\\\"
, " reframing:"
Expand Down Expand Up @@ -342,6 +338,10 @@ toLatex refDom datetime runref header clocksPdf ebsPdf topTikz ids SimConf{..} =
, "\\end{document}"
]
where
formatOffsets =
intercalate "; "
. (fmap (qtyPpm . roundDoubleInteger . fsToPpm refDom . floatToDouble))

qtyMs ms = "\\qty{" <> show ms <> "}{\\milli\\second}"
qtyPpm ppm = "\\qty{" <> show ppm <> "}{\\ppm}"

Expand Down
4 changes: 2 additions & 2 deletions bittide-experiments/src/Bittide/Simulate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ data SimPlotSettings = SimPlotSettings
, mode :: OutputMode
, dir :: FilePath
, stopStable :: Maybe Int
, fixClockOffs :: [Float]
, fixClockOffs :: Maybe [Float]
, fixStartDelays :: [Int]
, maxStartDelay :: Int
, sccc :: SomeClockControlConfig
Expand Down Expand Up @@ -234,7 +234,7 @@ simPlot# simSettings ccc t = do
givenClockOffsets =
V.unsafeFromList $
take (natToNum @nodes) $
(Just <$> fixClockOffs) <> repeat Nothing
sequenceA fixClockOffs <> repeat Nothing

givenStartupDelays =
V.unsafeFromList $
Expand Down
4 changes: 2 additions & 2 deletions bittide-experiments/src/Bittide/Simulate/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ data SimConf = SimConf
, stopAfterStable :: Maybe Int
-- ^ Stop simulation after all buffers have been stable for
-- at least the given number of clock cycles.
, clockOffsets :: [Float]
, clockOffsets :: Maybe [Float]
-- ^ The initital clock offsets in Femtoseconds
-- (randomly generated if missing).
, startupDelays :: [Int]
Expand Down Expand Up @@ -105,7 +105,7 @@ instance Default SimConf where
, waitTime = 100000
, stopWhenStable = False
, stopAfterStable = Nothing
, clockOffsets = []
, clockOffsets = Nothing
, startupDelays = []
, maxStartupDelay = 0
, createReport = False
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -510,7 +510,7 @@ tests =
, reframe = cccEnableReframing
, rusty = cccEnableRustySimulation
, waitTime = fromEnum cccReframingWaitTime
, clockOffsets = toList $ repeat @FpgaCount 0
, clockOffsets = Nothing
, startupDelays = toList $ repeat @FpgaCount 0
}
)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -683,7 +683,7 @@ tests =
, reframe = cccEnableReframing
, rusty = cccEnableRustySimulation
, waitTime = fromEnum cccReframingWaitTime
, clockOffsets = toList $ repeat @FpgaCount 0
, clockOffsets = Nothing
, startupDelays = toList $ repeat @FpgaCount 0
}
)
Expand Down
52 changes: 30 additions & 22 deletions bittide-instances/src/Bittide/Instances/Hitl/HwCcTopologies.hs
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ disabled =
{ fpgaEnabled = False
, calibrate = NoCCCalibration
, stepSizeSelect = commonStepSizeSelect
, initialClockShift = 0
, initialClockShift = Nothing
, startupDelay = 0
, mask = 0
}
Expand All @@ -160,10 +160,11 @@ data TestConfig = TestConfig
-- ^ The selected step size of the test. Note that changing the
-- step size between tests requires re-calibration of the device
-- based inital clock shift.
, initialClockShift :: InitialClockShift
, initialClockShift :: Maybe InitialClockShift
-- ^ Some artificical clock shift applied prior to the test
-- start. The shift is given in FINCs (if positive) or FDECs (if
-- negative) and, thus, depdends on 'stepSizeSelect'.
-- negative) and, thus, depdends on 'stepSizeSelect'. If 'Nothing',
-- no shift is applied.
, startupDelay :: StartupDelay
-- ^ Some intial startup delay given in the number of clock
-- cycles of the stable clock.
Expand Down Expand Up @@ -542,7 +543,7 @@ topologyTest refClk sysClk sysRst IlaControl{syncRst = rst, ..} rxNs rxPs miso c
adjusting = adjustStart .&&. (not <$> clocksAdjusted)
adjustRst = unsafeFromActiveLow adjustStart

initialAdjust = (+) <$> calibratedClockShift <*> (initialClockShift <$> cfg)
initialAdjust = (+) <$> calibratedClockShift <*> (fromMaybe 0 . initialClockShift <$> cfg)

adjustCount =
regEn
Expand Down Expand Up @@ -793,13 +794,13 @@ tests =
-----------

-- initial clock shifts startup delays topology
tt icsDiamond ((m *) <$> sdDiamond) diamond
, tt icsComplete ((m *) <$> sdComplete) $ complete d3
, tt icsCyclic ((m *) <$> sdCyclic) $ cyclic d5
, tt icsTorus ((m *) <$> sdTorus) $ torus2d d2 d3
, tt icsStar ((m *) <$> sdStar) $ star d7
, tt icsLine ((m *) <$> sdLine) $ line d4
, tt icsHourglass ((m *) <$> sdHourglass) $ hourglass d3
tt (Just icsDiamond) ((m *) <$> sdDiamond) diamond
, tt (Just icsComplete) ((m *) <$> sdComplete) $ complete d3
, tt (Just icsCyclic) ((m *) <$> sdCyclic) $ cyclic d5
, tt (Just icsTorus) ((m *) <$> sdTorus) $ torus2d d2 d3
, tt (Just icsStar) ((m *) <$> sdStar) $ star d7
, tt (Just icsLine) ((m *) <$> sdLine) $ line d4
, tt (Just icsHourglass) ((m *) <$> sdHourglass) $ hourglass d3
, -- CALIBRATION VERIFICATON --
-----------------------------
validateClockOffsetCalibration
Expand Down Expand Up @@ -860,13 +861,13 @@ tests =
then CCCalibrationValidation
else CCCalibrate
, stepSizeSelect = commonStepSizeSelect
, initialClockShift = 0
, initialClockShift = Nothing
, startupDelay = 0
, mask = maxBound
}
, defSimCfg
{ mTopologyType = Just $ Complete $ natToInteger @FpgaCount
, clockOffsets = toList $ repeat @FpgaCount 0
, clockOffsets = Nothing
, startupDelays = toList $ repeat @FpgaCount 0
}
)
Expand All @@ -876,16 +877,20 @@ tests =
tt ::
forall n.
(KnownNat n, n <= FpgaCount) =>
Vec n InitialClockShift ->
Maybe (Vec n InitialClockShift) ->
Vec n StartupDelay ->
Topology n ->
(TestName, (Probes TestConfig, SimConf))
tt clockShifts startDelays t =
( fromString $ topologyName t
,
( toList
( zipWith4 testData indicesI clockShifts startDelays
$ linkMasks @n t
( zipWith4
testData
indicesI
(maybeVecToVecMaybe clockShifts)
startDelays
(linkMasks @n t)
)
<> [ (fromInteger i, disabled)
| let n = natToNum @n
Expand All @@ -907,24 +912,27 @@ tests =
PPB_10 -> 100_000
PPB_100 -> 10_000
PPM_1 -> 1_000

fincFdecToFs = (/ stepSizeDiv) . (* clkPeriodPs) . fromIntegral
in
defSimCfg
{ mTopologyType = Just $ topologyType t
, clockOffsets =
(/ stepSizeDiv)
. (* clkPeriodPs)
. fromIntegral
<$> toList clockShifts
, clockOffsets = fmap fincFdecToFs . toList <$> clockShifts
, startupDelays = fromIntegral <$> toList startDelays
}
)
)

maybeVecToVecMaybe :: forall n a. (KnownNat n) => Maybe (Vec n a) -> Vec n (Maybe a)
maybeVecToVecMaybe = \case
Just v -> Just <$> v
Nothing -> repeat Nothing

testData ::
forall n.
(KnownNat n, n <= FpgaCount) =>
Index n ->
InitialClockShift ->
Maybe InitialClockShift ->
StartupDelay ->
BitVector LinkCount ->
(Index FpgaCount, TestConfig)
Expand Down
62 changes: 31 additions & 31 deletions bittide-tools/clockcontrol/plot/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -96,8 +96,8 @@ import Data.Csv.Conduit (
import Data.Functor ((<&>))
import Data.HashMap.Strict qualified as HashMap (fromList, size)
import Data.List (find, isPrefixOf, isSuffixOf, uncons)
import Data.Map qualified as Map (toList)
import Data.Maybe (catMaybes, fromJust, fromMaybe, isNothing, mapMaybe)
import Data.Map qualified as Map
import Data.Maybe (catMaybes, fromJust, fromMaybe, mapMaybe)
import Data.Proxy (Proxy (..))
import Data.Set qualified as Set (
difference,
Expand All @@ -110,6 +110,7 @@ import Data.String (fromString)
import Data.Text qualified as Text (unpack)
import Data.Vector qualified as Vector (fromList)
import GHC.IO.Exception (IOErrorType (..), IOException (..))
import GHC.Stack (HasCallStack)
import System.Directory (
createDirectoryIfMissing,
doesDirectoryExist,
Expand Down Expand Up @@ -548,24 +549,28 @@ fromCsvDump t i links (csvHandle, csvFile) =
{- | The HITL tests, whose post proc data offers a simulation config
for plotting.
-}
knownTestsWithSimConf :: [(String, [(String, Maybe SimConf)])]
knownTestsWithSimConf :: (HasCallStack) => [(String, [(String, SimConf)])]
knownTestsWithSimConf = hasSimConf <$> hitlTests
where
hasSimConf = \case
LoadConfig name _ -> (name, [])
KnownType name test ->
(name, first Text.unpack <$> Map.toList (mGetPPD @_ @SimConf test))
let !simConfMap = Map.mapMaybeWithKey justOrDie (mGetPPD @_ @SimConf test)
in (name, first Text.unpack <$> Map.toList simConfMap)

justOrDie _ (Just x) = Just x
justOrDie k Nothing = error $ "No SimConf for " <> show k

plotTest ::
(KnownDomain refDom) =>
Proxy refDom ->
FilePath ->
Maybe SimConf ->
SimConf ->
FilePath ->
FilePath ->
IO ()
plotTest refDom testDir mCfg dir globalOutDir = do
unless (isNothing mCfg) $ checkDependencies >>= maybe (return ()) die
plotTest refDom testDir cfg dir globalOutDir = do
checkDependencies >>= maybe (return ()) die
putStrLn $ "Creating plots for test case: " <> testName

let
Expand All @@ -581,9 +586,8 @@ plotTest refDom testDir mCfg dir globalOutDir = do
>>= \case
SomeNat n -> return $ STop $ complete $ snatProxy n

STop (t :: Topology topologySize) <- case mCfg of
Nothing -> topFromDirs
Just cfg -> case SimConf.mTopologyType cfg of
STop (t :: Topology topologySize) <-
case SimConf.mTopologyType cfg of
Nothing -> topFromDirs
Just (Random{}) -> topFromDirs
Just (DotFile f) -> readFile f >>= either die return . fromDot
Expand Down Expand Up @@ -656,27 +660,23 @@ plotTest refDom testDir mCfg dir globalOutDir = do
createDirectoryIfMissing True outDir
plot refDom outDir t $ Vec.unsafeFromList postProcessData

let allStable =
all
((\(_, _, _, xs) -> all (stable . snd) xs) . last)
postProcessData

case mCfg of
Nothing -> return ()
Just cfg' -> do
let cfg =
cfg'
{ SimConf.outDir = outDir
, SimConf.stable = Just allStable
}
ids = bimap toInteger fst <$> fpgas
case SimConf.mTopologyType cfg of
Nothing -> writeTop Nothing
Just (Random{}) -> writeTop Nothing
Just (DotFile f) -> readFile f >>= writeTop . Just
Just tt -> fromTopologyType tt >>= either die (`saveSimConfig` cfg)
checkIntermediateResults outDir
>>= maybe (generateReport (Proxy @Basic125) "HITLT Report" outDir ids cfg) die
let
allStable =
all ((\(_, _, _, xs) -> all (stable . snd) xs) . last) postProcessData
cfg1 =
cfg
{ SimConf.outDir = outDir
, SimConf.stable = Just allStable
}
ids = bimap toInteger fst <$> fpgas

case SimConf.mTopologyType cfg of
Nothing -> writeTop Nothing
Just (Random{}) -> writeTop Nothing
Just (DotFile f) -> readFile f >>= writeTop . Just
Just tt -> fromTopologyType tt >>= either die (`saveSimConfig` cfg1)
checkIntermediateResults outDir
>>= maybe (generateReport (Proxy @Basic125) "HITLT Report" outDir ids cfg1) die
_ -> die "Empty topology"
_ -> die "Topology is larger than expected"
where
Expand Down
2 changes: 1 addition & 1 deletion bittide-tools/clockcontrol/sim/src/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ main = do
let cfg =
simCfg
{ stable = isStable
, clockOffsets = clockOffs
, clockOffsets = Just clockOffs
, startupDelays = startDelays
}
saveSimConfig t cfg
Expand Down

0 comments on commit 0de395a

Please sign in to comment.