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 ae24d9d
Show file tree
Hide file tree
Showing 19 changed files with 117 additions and 171 deletions.
45 changes: 13 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,25 @@ 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

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))
HitlTestCase h a b

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 +275,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
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,7 @@ import Bittide.Instances.Hitl.Utils.Program
import Bittide.Instances.Hitl.Utils.Vivado
import Control.Exception
import Control.Monad.Extra
import Data.Either (partitionEithers)
import qualified Data.List as L
import Data.Maybe
import Numeric
Expand Down Expand Up @@ -63,14 +64,26 @@ 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

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

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 +93,16 @@ 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
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 Down
34 changes: 19 additions & 15 deletions bittide-instances/src/Bittide/Instances/Hitl/Driver/VexRiscv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,15 +27,17 @@ import Bittide.Instances.Hitl.Utils.Program
import Bittide.Instances.Hitl.Utils.Vivado

import Control.Concurrent (threadDelay)
import Control.Exception (SomeException, catch, displayException)
import Control.Monad (forM)
import Control.Exception (SomeException, displayException, handle)
import Control.Monad (forM, forM_, unless)
import Data.Either (partitionEithers)
import qualified Data.List as L
import Data.Maybe (fromJust, fromMaybe)
import System.Exit
import System.FilePath
import System.IO
import System.Process
import System.Timeout (timeout)
import Test.Tasty.HUnit (assertFailure)

preProcessFunc ::
VivadoHandle ->
Expand Down Expand Up @@ -151,27 +153,34 @@ driverFunc ::
VivadoHandle ->
String ->
FilePath ->
[ ( HwTarget
, DeviceInfo
, ()
)
] ->
[(HwTarget, DeviceInfo)] ->
IO ExitCode
driverFunc v _name ilaPath targets = do
putStrLn
$ "Running Driver function for targets "
<> show ((\(_, info, _) -> info.deviceId) <$> targets)
<> show ((\(_, info) -> info.deviceId) <$> targets)

preProcessResults <- forM targets $ \(hwT, dI) -> do
preProcessFunc v _name ilaPath hwT dI >>= \case
TestStepSuccess out -> pure $ Right out
TestStepFailure reason -> pure $ Left reason

let (preProcessFails, preProcessPasses) = partitionEithers preProcessResults

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

let
catchError :: DeviceInfo -> SomeException -> IO ExitCode
catchError d ex = do
putStrLn $ "Test Failed on device " <> d.deviceId <> " with: " <> displayException ex
pure $ ExitFailure 2

exitCodes <- forM targets $ \(hwT, d, ()) -> flip catch (catchError d) $ do
exitCodes <- forM (L.zip targets preProcessPasses) $ \((hwT, d), _) -> handle (catchError d) $ do
putStrLn $ "Running driver for " <> d.deviceId


openHwT v hwT
execCmd_ v "set_property" ["PROBES.FILE", embrace ilaPath, "[current_hw_device]"]
refresh_hw_device v []
Expand All @@ -185,9 +194,7 @@ driverFunc v _name ilaPath targets = do
let targetIndex = fromMaybe 9 $ L.findIndex (\di -> di.deviceId == targetId) demoRigInfo
-- since we're running one test after another we don't need a different port
let gdbPort = 3333 -- + targetIndex

withOpenOcd d.usbAdapterLocation gdbPort $ \ocd -> do

-- make sure OpenOCD is started properly

hSetBuffering ocd.stderrHandle LineBuffering
Expand All @@ -205,7 +212,6 @@ driverFunc v _name ilaPath targets = do

putStrLn "Starting Picocom..."
withPicocomWithLogging d.serial stdoutLog stderrLog $ \pico -> do

hSetBuffering pico.stdinHandle LineBuffering
hSetBuffering pico.stdoutHandle LineBuffering

Expand Down Expand Up @@ -235,7 +241,6 @@ driverFunc v _name ilaPath targets = do

-- program the FPGA
withGdb $ \gdb -> do

hSetBuffering gdb.stdinHandle LineBuffering

runGdbCommands
Expand All @@ -249,7 +254,6 @@ driverFunc v _name ilaPath targets = do
tryWithTimeout "Waiting for \"load dome\"" 120_000_000
$ waitForLine gdb.stdoutHandle "load done"


-- break test
do
putStrLn "Testing whether breakpoints work"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -178,13 +178,15 @@ driverFunc ::
VivadoHandle ->
String ->
FilePath ->
[ ( HwTarget
, DeviceInfo
, (ProcessStdIoHandles, ProcessStdIoHandles, ProcessStdIoHandles, IO ())
)
] ->
[(HwTarget, DeviceInfo)] ->
IO ExitCode
driverFunc v _name ilaPath [(hwT, _, (_ocd, pico, _gdb, cleanupFn))] = do
driverFunc v _name ilaPath [(hwT, dI)] = do
preProcessResult <- preProcessFunc v _name ilaPath hwT dI

(_ocd, pico, _gdb, cleanupFn) <- case preProcessResult of
TestStepSuccess out -> pure out
TestStepFailure reason -> assertFailure $ "test failed. reason: " <> reason

openHwT v hwT
execCmd_ v "set_property" ["PROBES.FILE", embrace ilaPath, "[current_hw_device]"]
refresh_hw_device v []
Expand Down Expand Up @@ -238,7 +240,7 @@ driverFunc v _name ilaPath [(hwT, _, (_ocd, pico, _gdb, cleanupFn))] = do

cleanupFn

pure $ ExitSuccess
pure ExitSuccess
driverFunc _v _name _ilaPath _ = error "Ethernet/VexRiscvTcp driver func should only run with one hardware target"

{- | Test that the `Bittide.Instances.Hitl.Ethernet:vexRiscvTcpTest` design programmed
Expand Down
2 changes: 0 additions & 2 deletions bittide-instances/src/Bittide/Instances/Hitl/Ethernet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,10 +89,8 @@ tests =
{ name = "VexRiscvTcp"
, parameters = paramForSingleHwTarget (HwTargetByIndex 7) ()
, postProcData = ()
, preProc = InheritPreProcess
}
]
, mPreProc = preProcessFunc
, mDriverProc = Just driverFunc
, mPostProc = Nothing
}
2 changes: 0 additions & 2 deletions bittide-instances/src/Bittide/Instances/Hitl/FincFdec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,6 @@ import Bittide.Hitl (
HitlTestGroup (..),
HwTargetRef (HwTargetByIndex),
hitlVio,
noPreProcess,
testCasesFromEnum,
)
import Bittide.Instances.Domains
Expand Down Expand Up @@ -223,7 +222,6 @@ tests =
, extraXdcFiles = []
, externalHdl = []
, testCases = testCasesFromEnum @Test [HwTargetByIndex 7] ()
, mPreProc = noPreProcess
, mDriverProc = Nothing
, mPostProc = Nothing
}
2 changes: 0 additions & 2 deletions bittide-instances/src/Bittide/Instances/Hitl/FullMeshHwCc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -540,10 +540,8 @@ mkTest topEntity =
, clockOffsets = Nothing
, startupDelays = toList $ repeat @FpgaCount 0
}
, preProc = InheritPreProcess
}
]
, mPreProc = noPreProcess
, mDriverProc = Nothing
, mPostProc = Nothing
}
Expand Down
Loading

0 comments on commit ae24d9d

Please sign in to comment.