diff --git a/clash-vexriscv-sim/src/Utils/Cpu.hs b/clash-vexriscv-sim/src/Utils/Cpu.hs index faed33f..c5bcf07 100644 --- a/clash-vexriscv-sim/src/Utils/Cpu.hs +++ b/clash-vexriscv-sim/src/Utils/Cpu.hs @@ -106,8 +106,8 @@ cpu jtagPort bootIMem bootDMem = { timerInterrupt = low, externalInterrupt = low, softwareInterrupt = low, - iBusWbS2M = makeDefined iBus, - dBusWbS2M = makeDefined dBus + iBusWbS2M = iBus, + dBusWbS2M = dBus } ) <$> iS2M diff --git a/clash-vexriscv/clash-vexriscv.cabal b/clash-vexriscv/clash-vexriscv.cabal index 7ae96cb..9a22c48 100644 --- a/clash-vexriscv/clash-vexriscv.cabal +++ b/clash-vexriscv/clash-vexriscv.cabal @@ -112,6 +112,7 @@ library VexRiscv.ClockTicks VexRiscv.FFI VexRiscv.JtagTcpBridge + VexRiscv.Random VexRiscv.TH VexRiscv.VecToTuple @@ -126,6 +127,7 @@ library Glob, network, process >= 1.6 && < 1.8, + random, string-interpolate, tagged, template-haskell, @@ -141,9 +143,11 @@ test-suite unittests other-modules: Tests.Extra Tests.VexRiscv.ClockTicks + Tests.VexRiscv.Random build-depends: HUnit, base, + clash-prelude-hedgehog, clash-vexriscv, bytestring, hedgehog >= 1.0 && < 1.5, diff --git a/clash-vexriscv/src/VexRiscv.hs b/clash-vexriscv/src/VexRiscv.hs index fd33dbf..7aab01c 100644 --- a/clash-vexriscv/src/VexRiscv.hs +++ b/clash-vexriscv/src/VexRiscv.hs @@ -31,6 +31,7 @@ import Protocols.Wishbone import VexRiscv.ClockTicks import VexRiscv.FFI +import VexRiscv.Random import VexRiscv.TH import VexRiscv.VecToTuple @@ -71,20 +72,6 @@ instance Protocol (Jtag dom) where type Fwd (Jtag dom) = Signal dom JtagIn type Bwd (Jtag dom) = Signal dom JtagOut - --- When passing S2M values from Haskell to VexRiscv over the FFI, undefined --- bits/values cause errors when forcing their evaluation to something that can --- be passed through the FFI. --- --- This function makes sure the Wishbone S2M values are free from undefined bits. -makeDefined :: WishboneS2M (BitVector 32) -> WishboneS2M (BitVector 32) -makeDefined wb = wb {readData = defaultX 0 (readData wb)} - -defaultX :: (NFDataX a) => a -> a -> a -defaultX dflt val - | hasUndefined val = dflt - | otherwise = val - vexRiscv :: forall dom . ( HasCallStack @@ -136,16 +123,10 @@ vexRiscv clk rst cpuInput jtagInput = = (\(CpuIn a b c d e) -> (a, b, c, d, e)) <$> cpuInput (unbundle -> (iBus_DAT_MISO, iBus_ACK, iBus_ERR)) - = (\(WishboneS2M a b c _ _) -> (a, b, c)) - -- A hack that enables us to both generate synthesizable HDL and simulate vexRisc in Haskell/Clash - . (if clashSimulation then makeDefined else id) - <$> iBusS2M + = (\(WishboneS2M a b c _ _) -> (a, b, c)) <$> iBusS2M (unbundle -> (dBus_DAT_MISO, dBus_ACK, dBus_ERR)) - = (\(WishboneS2M a b c _ _) -> (a, b, c)) - -- A hack that enables us to both generate synthesizable HDL and simulate vexRisc in Haskell/Clash - . (if clashSimulation then makeDefined else id) - <$> dBusS2M + = (\(WishboneS2M a b c _ _) -> (a, b, c)) <$> dBusS2M (unbundle -> (jtag_TCK, jtag_TMS, jtag_TDI)) = bitCoerce <$> jtagInput @@ -243,39 +224,55 @@ vexRiscv# , Signal dom Bit -- ^ jtag_TDO ) vexRiscv# !_sourcePath clk rst0 - timerInterrupt - externalInterrupt - softwareInterrupt - iBus_ACK - iBus_ERR - iBus_DAT_MISO - - dBus_ACK - dBus_ERR - dBus_DAT_MISO - - jtag_TCK - jtag_TMS - jtag_TDI = unsafePerformIO $ do + timerInterrupt0 + externalInterrupt0 + softwareInterrupt0 + iBus_ACK0 + iBus_ERR0 + iBus_DAT_MISO0 + + dBus_ACK0 + dBus_ERR0 + dBus_DAT_MISO0 + + jtag_TCK0 + jtag_TMS0 + jtag_TDI0 = unsafePerformIO $ do (v, initStage1, initStage2, stepRising, stepFalling, _shutDown) <- vexCPU + -- Make sure all the inputs are defined + let + rst1 = unsafeMakeDefinedRandom <$> unsafeToActiveHigh rst0 + timerInterrupt1 = unsafeMakeDefinedRandom <$> timerInterrupt0 + externalInterrupt1 = unsafeMakeDefinedRandom <$> externalInterrupt0 + softwareInterrupt1 = unsafeMakeDefinedRandom <$> softwareInterrupt0 + iBus_ACK1 = unsafeMakeDefinedRandom <$> iBus_ACK0 + iBus_DAT_MISO1 = unsafeMakeDefinedRandom <$> iBus_DAT_MISO0 + iBus_ERR1 = unsafeMakeDefinedRandom <$> iBus_ERR0 + dBus_ACK1 = unsafeMakeDefinedRandom <$> dBus_ACK0 + dBus_DAT_MISO1 = unsafeMakeDefinedRandom <$> dBus_DAT_MISO0 + dBus_ERR1 = unsafeMakeDefinedRandom <$> dBus_ERR0 + jtag_TCK1 = unsafeMakeDefinedRandom <$> jtag_TCK0 + jtag_TMS1 = unsafeMakeDefinedRandom <$> jtag_TMS0 + jtag_TDI1 = unsafeMakeDefinedRandom <$> jtag_TDI0 + let nonCombInput = NON_COMB_INPUT - <$> (boolToBit <$> unsafeToActiveHigh rst0) - <*> timerInterrupt - <*> externalInterrupt - <*> softwareInterrupt + <$> (boolToBit <$> rst1) + <*> timerInterrupt1 + <*> externalInterrupt1 + <*> softwareInterrupt1 combInput = COMB_INPUT - <$> (boolToBit <$> iBus_ACK) - <*> (unpack <$> iBus_DAT_MISO) - <*> (boolToBit <$> iBus_ERR) - <*> (boolToBit <$> dBus_ACK) - <*> (unpack <$> dBus_DAT_MISO) - <*> (boolToBit <$> dBus_ERR) - <*> jtag_TCK - <*> jtag_TMS - <*> jtag_TDI + <$> (boolToBit <$> iBus_ACK1) + <*> (unpack <$> iBus_DAT_MISO1) + <*> (boolToBit <$> iBus_ERR1) + <*> (boolToBit <$> dBus_ACK1) + <*> (unpack <$> dBus_DAT_MISO1) + <*> (boolToBit <$> dBus_ERR1) + <*> jtag_TCK1 + <*> jtag_TMS1 + <*> jtag_TDI1 simInitThenCycles :: Signal dom NON_COMB_INPUT -> diff --git a/clash-vexriscv/src/VexRiscv/Random.hs b/clash-vexriscv/src/VexRiscv/Random.hs new file mode 100644 index 0000000..38c2da9 --- /dev/null +++ b/clash-vexriscv/src/VexRiscv/Random.hs @@ -0,0 +1,49 @@ +-- SPDX-FileCopyrightText: 2024 Google LLC +-- +-- SPDX-License-Identifier: Apache-2.0 +{-# LANGUAGE CPP #-} + +module VexRiscv.Random where + +import Clash.Prelude + +#if __GLASGOW_HASKELL__ <= 902 +import Numeric.Natural +#endif + +import Clash.Sized.Internal.BitVector +import Data.Bifunctor (bimap) +import GHC.IO (unsafePerformIO) +import System.Random + +-- | Unsafe version of 'makeDefinedRandom' with a NOINLINE pragma to avoid +-- compiler optimizations. +unsafeMakeDefinedRandom :: DefinedRandom a => a -> a +unsafeMakeDefinedRandom = unsafePerformIO . makeDefinedRandom +{-# NOINLINE unsafeMakeDefinedRandom #-} + +-- | A class for types that can be (partially) undefined whose undefined values +-- can be replaced with defined random values. +class DefinedRandom a where + makeDefinedRandom :: a -> IO a + +instance DefinedRandom Bool where + makeDefinedRandom b + | hasUndefined b = randomIO + | otherwise = pure b + +instance DefinedRandom Bit where + makeDefinedRandom b + | hasUndefined b = Bit 0 <$> randomRIO (0, 1) + | otherwise = pure b + +instance KnownNat n => DefinedRandom (BitVector n) where + makeDefinedRandom :: KnownNat n => BitVector n -> IO (BitVector n) + makeDefinedRandom (ensureSpine -> BV mask dat) = do + let maxVal = natToNum @(2^n - 1) + randomInt <- genNatural (0, fromIntegral maxVal) + pure $ BV 0 (((maxVal `xor` mask) .&. dat) .|. (mask .&. randomInt)) + +-- | Generate a random natural number in the given inclusive range. +genNatural :: (Natural, Natural) -> IO Natural +genNatural = fmap fromInteger . randomRIO . bimap toInteger toInteger diff --git a/clash-vexriscv/tests/unittests/Tests/VexRiscv/Random.hs b/clash-vexriscv/tests/unittests/Tests/VexRiscv/Random.hs new file mode 100644 index 0000000..910cac5 --- /dev/null +++ b/clash-vexriscv/tests/unittests/Tests/VexRiscv/Random.hs @@ -0,0 +1,44 @@ +-- SPDX-FileCopyrightText: 2024 Google LLC +-- +-- SPDX-License-Identifier: Apache-2.0 +module Tests.VexRiscv.Random where + +import Clash.Prelude + +import Clash.Hedgehog.Sized.BitVector +import Hedgehog +import Test.Tasty +import Test.Tasty.Hedgehog +import VexRiscv.Random + +import qualified Hedgehog.Gen as Gen +import qualified Hedgehog.Range as Range + +tests :: TestTree +tests = testGroup "VexRiscv.Random" + [ testProperty "genNatural" prop_genNatural + , testProperty "makeDefinedRandomBitVector" prop_makeDefinedRandomBitVector + , testProperty "makeDefinedRandomBit" prop_makeDefinedRandomBit + ] + +prop_genNatural :: Property +prop_genNatural = property $ do + lo <- forAll $ Gen.integral (Range.linear 0 (shiftL 1 1024)) + hi <- forAll $ Gen.integral (Range.linear lo (shiftL 1 1024)) + n <- evalIO $ genNatural (lo, hi) + assert ((n >= lo) && (n <= hi)) + +prop_makeDefinedRandomBitVector :: Property +prop_makeDefinedRandomBitVector = property $ do + someBv <- forAll $ (genSomeBitVector @_ @0) (Range.linear 0 1024) genBitVector + case someBv of + SomeBitVector SNat bv -> do + definedBv <- evalIO $ makeDefinedRandom bv + assert (not $ hasUndefined definedBv) + assert (definedBv <= maxBound) + +prop_makeDefinedRandomBit :: Property +prop_makeDefinedRandomBit = property $ do + b <- forAll $ genBit + definedB <- evalIO $ makeDefinedRandom b + assert (not $ hasUndefined definedB) diff --git a/clash-vexriscv/tests/unittests/main.hs b/clash-vexriscv/tests/unittests/main.hs index 4793f75..03a50be 100644 --- a/clash-vexriscv/tests/unittests/main.hs +++ b/clash-vexriscv/tests/unittests/main.hs @@ -10,10 +10,12 @@ import Test.Tasty import Test.Tasty.Hedgehog import qualified Tests.VexRiscv.ClockTicks +import qualified Tests.VexRiscv.Random tests :: TestTree tests = testGroup "Tests" [ Tests.VexRiscv.ClockTicks.tests + , Tests.VexRiscv.Random.tests ] setDefaultHedgehogTestLimit :: HedgehogTestLimit -> HedgehogTestLimit