Skip to content

Commit

Permalink
No more pre-processing ):
Browse files Browse the repository at this point in the history
  • Loading branch information
rslawson committed Dec 13, 2024
1 parent 884bdaf commit 7893ced
Show file tree
Hide file tree
Showing 20 changed files with 173 additions and 206 deletions.
44 changes: 12 additions & 32 deletions bittide-experiments/src/Bittide/Hitl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,6 @@ module Bittide.Hitl (
-- * Test definition
HitlTestGroup (..),
HitlTestCase (..),
CasePreProcessing (..),
TestStepResult (..),
MayHavePostProcData (..),
Done,
Expand Down Expand Up @@ -189,26 +188,21 @@ and requires a (hypothetical) 8-bit number indicating the
> , postProcData = ()
> }
> ]
> , mPreProc = Nothing
> , mPostProc = Nothing
> }
This must be accompanied by a @hitlVio \@NumberOfStages@ in the design.
-}
data HitlTestGroup where
HitlTestGroup ::
(Typeable a, Typeable b, Typeable c) =>
(Typeable a, Typeable b) =>
{ topEntity :: ClashTargetName
-- ^ Reference to the Design Under Test
, extraXdcFiles :: [String]
, testCases :: [HitlTestCase HwTargetRef a b c]
, testCases :: [HitlTestCase HwTargetRef a b]
-- ^ List of test cases
, mPreProc ::
( VivadoHandle -> String -> FilePath -> HwTarget -> DeviceInfo -> IO (TestStepResult c)
)
-- ^ Pre-processing step. First argument is the name of the test
, mDriverProc ::
Maybe (VivadoHandle -> String -> FilePath -> [(HwTarget, DeviceInfo, c)] -> IO ExitCode)
Maybe (VivadoHandle -> String -> FilePath -> [(HwTarget, DeviceInfo)] -> IO ExitCode)
-- ^ Optional function driving the test after pre-processing.
, mPostProc :: Maybe (FilePath -> ExitCode -> IO (TestStepResult ()))
-- ^ Optional post processing step.
Expand All @@ -220,36 +214,24 @@ data HitlTestGroup where
{- | A HITL test case. One HITL test group can have multiple test cases
associated with it.
-}
data HitlTestCase h a b c where
data HitlTestCase h a b where
HitlTestCase ::
(Show h, Show a, BitPack a, Show b, Typeable h, Typeable c) =>
(Show h, Show a, BitPack a, Show b, Typeable h) =>
{ name :: String
, parameters :: Map h a
, preProc :: CasePreProcessing c
, postProcData :: b
} ->
HitlTestCase h a b c
HitlTestCase h a b

deriving instance Show (HitlTestCase h a b c)

data CasePreProcessing c
= InheritPreProcess
| -- | Instead of using the test-group pre-process function, use an override for
-- this specific test case.
CustomPreProcess
(VivadoHandle -> FilePath -> HwTarget -> DeviceInfo -> IO (TestStepResult c))

instance Show (CasePreProcessing a) where
show InheritPreProcess = "InheritPreProcess"
show (CustomPreProcess _) = "CustomPreProcess <func>"
deriving instance Show (HitlTestCase h a b)

-- | A class for extracting optional post processing data from a test.
class MayHavePostProcData b where
-- | Returns the test names with some post processing data of type @c@,
-- if that data exists.
mGetPPD ::
forall h a c.
[HitlTestCase h a b c] ->
forall h a.
[HitlTestCase h a b] ->
Map String (Maybe b)

instance MayHavePostProcData a where
Expand Down Expand Up @@ -292,26 +274,24 @@ to it and receives that constructur as test parameter.
> testCases = testCasesFromEnum @ABC allHwTargets ()
-}
testCasesFromEnum ::
forall a b c.
-- forall a b c.
forall a b.
( Show a
, Bounded a
, Enum a
, BitPack a
, Show b
, Show c
, Typeable a
, Typeable b
, Typeable c
) =>
[HwTargetRef] ->
b ->
[HitlTestCase HwTargetRef a b c]
[HitlTestCase HwTargetRef a b]
testCasesFromEnum hwTs ppd =
[ HitlTestCase
{ name = show constr
, parameters = Map.fromList ((,constr) <$> hwTs)
, postProcData = ppd
, preProc = InheritPreProcess
}
| (constr :: a) <- [minBound ..]
]
Expand Down
4 changes: 3 additions & 1 deletion bittide-instances/data/picocom/start.sh
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ PICOCOM_STDERR_LOG="${PICOCOM_STDERR_LOG:-/dev/null}"
stderr_dir=$(dirname "${PICOCOM_STDERR_LOG}")
mkdir -p "${stderr_dir}"

picocom --baud 921600 --imap lfcrlf --omap lfcrlf $@ \
PICOCOM_BAUD="${PICOCOM_BAUD:-921600}"

picocom --baud "${PICOCOM_BAUD}" --imap lfcrlf --omap lfcrlf $@ \
> >(tee "${PICOCOM_STDOUT_LOG}") \
2> >(tee "${PICOCOM_STDERR_LOG}" >&2)
9 changes: 3 additions & 6 deletions bittide-instances/src/Bittide/Instances/Hitl/BoardTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,11 @@ import Bittide.Instances.Hitl.Post.BoardTestExtended
import Bittide.Instances.Hitl.Post.PostProcess

import Bittide.Hitl (
CasePreProcessing (..),
HitlTestCase (..),
HitlTestGroup (..),
TestStepResult (..),
hitlVio,
hitlVioBool,
noPreProcess,
paramForHwTargets,
testCasesFromEnum,
)
Expand Down Expand Up @@ -189,11 +187,11 @@ testSimple =
{ name = "Simple"
, parameters = (paramForHwTargets allHwTargets ())
, postProcData = ()
, preProc = InheritPreProcess
-- , preProc = InheritPreProcess
}
]
, mPreProc = noPreProcess
, mDriverProc = Nothing
, -- , mPreProc = noPreProcess
mDriverProc = Nothing
, mPostProc = Nothing
}

Expand All @@ -204,7 +202,6 @@ testExtended =
, extraXdcFiles = []
, externalHdl = []
, testCases = testCasesFromEnum @Test allHwTargets ()
, mPreProc = noPreProcess
, mDriverProc = Nothing
, mPostProc = Just postBoardTestExtendedFunc
}
Expand Down
2 changes: 0 additions & 2 deletions bittide-instances/src/Bittide/Instances/Hitl/DnaOverSerial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,10 +97,8 @@ tests =
{ name = "DnaOverSerial"
, parameters = paramForHwTargets allHwTargets ()
, postProcData = ()
, preProc = InheritPreProcess
}
]
, mPreProc = dnaOverSerialPreProcess
, mDriverProc = Just dnaOverSerialDriver
, mPostProc = Nothing
}
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,8 @@ import Bittide.Instances.Hitl.Utils.Program
import Bittide.Instances.Hitl.Utils.Vivado
import Control.Exception
import Control.Monad.Extra
import Data.Char (isHexDigit)
import Data.Either (partitionEithers)
import qualified Data.List as L
import Data.Maybe
import Numeric
Expand Down Expand Up @@ -49,7 +51,12 @@ dnaOverSerialPreProcess _v _name _ilaPath hwT deviceInfo = do
stderrLog = hitlDir </> "picocom-stderr." <> show targetIndex <> ".log"
putStrLn $ "logging stdout to `" <> stdoutLog <> "`"
putStrLn $ "logging stderr to `" <> stderrLog <> "`"
(pico, picoClean) <- startPicocomWithLogging deviceInfo.serial stdoutLog stderrLog
(pico, picoClean) <-
startPicocomWithLoggingAndEnv
deviceInfo.serial
stdoutLog
stderrLog
[("PICOCOM_BAUD", "9600")]

hSetBuffering pico.stdinHandle LineBuffering
hSetBuffering pico.stdoutHandle LineBuffering
Expand All @@ -63,14 +70,30 @@ dnaOverSerialDriver ::
VivadoHandle ->
String ->
FilePath ->
[(HwTarget, DeviceInfo, (ProcessStdIoHandles, IO ()))] ->
[(HwTarget, DeviceInfo)] ->
IO ExitCode
dnaOverSerialDriver v _name ilaPath targets = do
flip finally (forM targets $ \(_, _, (_, cleanup)) -> cleanup) $ do
preProcessResults <- forM targets $ \(hwT, dI) -> do
dnaOverSerialPreProcess v _name ilaPath hwT dI >>= \case
TestStepSuccess out -> pure $ Right out
TestStepFailure reason -> pure $ Left reason

putStrLn "Attempted to open Picocom for all target devices"

let (preProcessFails, preProcessPasses) = partitionEithers preProcessResults

unless (null preProcessFails) $ do
let failReason = "Some preprocess steps failed. reasons:\n - " <> L.intercalate "\n - " preProcessFails
forM_ preProcessPasses snd
assertFailure failReason

putStrLn "No failures for Picocom opening"

flip finally (forM preProcessPasses snd) $ do
putStrLn "Starting all targets to read DNA values"

-- start all targets
forM_ targets $ \(hwT, _, _) -> do
forM_ targets $ \(hwT, _) -> do
openHwT v hwT
execCmd_ v "set_property" ["PROBES.FILE", embrace ilaPath, "[current_hw_device]"]
refresh_hw_device v []
Expand All @@ -80,16 +103,17 @@ dnaOverSerialDriver v _name ilaPath targets = do

putStrLn "Expecting specific DNAs for all serial ports"
putStrLn "Serial ports:"
mapM_ putStrLn [d.serial | (_, d, _) <- targets]
mapM_ putStrLn [d.serial | (_, d) <- targets]

results <- forM targets $ \(_, d, (picoCom, picoClean)) -> do
results <- forM (L.zip targets preProcessPasses) $ \((_, d), (picoCom, picoClean)) -> do
putStrLn $ "Waiting for output on port: " <> d.serial
res <- checkDna d picoCom
picoClean
pure $ res
pure res

print results
if (and results)
then pure $ ExitSuccess
if and results
then pure ExitSuccess
else do
assertFailure "Not all FPGAs transmitted the expected DNA"
pure $ ExitFailure 2
Expand All @@ -101,8 +125,12 @@ dnaOverSerialDriver v _name ilaPath targets = do
when (isNothing terminalReadyResult) $ do
assertFailure "Timeout waiting for \"Terminal ready\""

_ <- hGetLine pico.stdoutHandle -- Discard a potentially incomplete line
receivedDna <- hGetLine pico.stdoutHandle
putStrLn "Terminal is ready!"

receivedDna0 <- timeout 10_000_000 $ findDna pico ""
receivedDna <- case receivedDna0 of
Just rDna -> return rDna
Nothing -> assertFailure "Timeout waiting for DNA"
let
expected = showHex d.dna ""
differences = L.zipWith (\e a -> if e == a then ' ' else '^') expected receivedDna
Expand All @@ -112,3 +140,12 @@ dnaOverSerialDriver v _name ilaPath targets = do
putStrLn $ "Received DNA: " <> receivedDna
putStrLn $ "Differences: " <> differences
pure match
findDna :: ProcessStdIoHandles -> String -> IO String
findDna pico prev = do
nC <- hGetChar pico.stdoutHandle
if isHexDigit nC
then findDna pico (prev <> [nC])
else
if null prev
then findDna pico prev
else return prev
Loading

0 comments on commit 7893ced

Please sign in to comment.