Skip to content

Commit

Permalink
Add randomly generated values for undefined bits in FFI
Browse files Browse the repository at this point in the history
  • Loading branch information
lmbollen committed Apr 4, 2024
1 parent 1156fda commit 05ec8b0
Show file tree
Hide file tree
Showing 5 changed files with 111 additions and 13 deletions.
3 changes: 3 additions & 0 deletions clash-vexriscv/clash-vexriscv.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ library
hs-source-dirs: src
default-language: Haskell2010
exposed-modules:
VexRiscv.Random
VexRiscv
VexRiscv.ClockTicks
VexRiscv.FFI
Expand All @@ -126,6 +127,7 @@ library
Glob,
network,
process >= 1.6 && < 1.8,
random,
string-interpolate,
tagged,
template-haskell,
Expand All @@ -141,6 +143,7 @@ test-suite unittests
other-modules:
Tests.Extra
Tests.VexRiscv.ClockTicks
Tests.VexRiscv.Random
build-depends:
HUnit,
base,
Expand Down
43 changes: 30 additions & 13 deletions clash-vexriscv/src/VexRiscv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ import VexRiscv.ClockTicks
import VexRiscv.FFI
import VexRiscv.TH
import VexRiscv.VecToTuple
import VexRiscv.Random

import qualified VexRiscv.FFI as FFI

Expand Down Expand Up @@ -259,23 +260,39 @@ vexRiscv# !_sourcePath clk rst0
jtag_TDI = unsafePerformIO $ do
(v, initStage1, initStage2, stepRising, stepFalling, _shutDown) <- vexCPU

-- Make sure all the inputs are defined
let
rst0' = unsafePerformIO . makeDefinedRandom <$> unsafeToActiveHigh rst0
timerInterrupt' = unsafePerformIO . makeDefinedRandom <$> timerInterrupt
externalInterrupt' = unsafePerformIO . makeDefinedRandom <$> externalInterrupt
softwareInterrupt' = unsafePerformIO . makeDefinedRandom <$> softwareInterrupt
iBus_ACK' = unsafePerformIO . makeDefinedRandom <$> iBus_ACK
iBus_DAT_MISO' = unsafePerformIO . makeDefinedRandom <$> iBus_DAT_MISO
iBus_ERR' = unsafePerformIO . makeDefinedRandom <$> iBus_ERR
dBus_ACK' = unsafePerformIO . makeDefinedRandom <$> dBus_ACK
dBus_DAT_MISO' = unsafePerformIO . makeDefinedRandom <$> dBus_DAT_MISO
dBus_ERR' = unsafePerformIO . makeDefinedRandom <$> dBus_ERR
jtag_TCK' = unsafePerformIO . makeDefinedRandom <$> jtag_TCK
jtag_TMS' = unsafePerformIO . makeDefinedRandom <$> jtag_TMS
jtag_TDI' = unsafePerformIO . makeDefinedRandom <$> jtag_TDI

let
nonCombInput = NON_COMB_INPUT
<$> (boolToBit <$> unsafeToActiveHigh rst0)
<*> timerInterrupt
<*> externalInterrupt
<*> softwareInterrupt
<$> (boolToBit <$> rst0')
<*> timerInterrupt'
<*> externalInterrupt'
<*> softwareInterrupt'

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_ACK')
<*> (unpack <$> iBus_DAT_MISO')
<*> (boolToBit <$> iBus_ERR')
<*> (boolToBit <$> dBus_ACK')
<*> (unpack <$> dBus_DAT_MISO')
<*> (boolToBit <$> dBus_ERR')
<*> jtag_TCK'
<*> jtag_TMS'
<*> jtag_TDI'

simInitThenCycles ::
Signal dom NON_COMB_INPUT ->
Expand Down
49 changes: 49 additions & 0 deletions clash-vexriscv/src/VexRiscv/Random.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,49 @@
-- SPDX-FileCopyrightText: 2024 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0
module VexRiscv.Random where

import Clash.Prelude
import Numeric.Natural
import Clash.Sized.Internal.BitVector
import System.Random

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@(Bit 0 _) = pure b
makeDefinedRandom _ = do
d <- randomRIO (0, 1)
pure (Bit 1 d)

instance KnownNat n => DefinedRandom (BitVector n) where
makeDefinedRandom :: KnownNat n => BitVector n -> IO (BitVector n)
makeDefinedRandom (BV mask dat) = do
let
(BV _ maxVal) = (maxBound :: BitVector n)
(BV maxMask _) = deepErrorX "" :: BitVector n
randomInt <- genNatural (0, fromIntegral maxVal)

pure $ BV 0 ((dat .&. (maxMask `xor` mask)) .|. (randomInt .&. mask))

genNatural :: (Natural, Natural) -> IO Natural
genNatural (lo, hi)
| lo > hi = error "genNatural: lower bound > upper bound"
| otherwise = (lo +) <$> go (hi - lo)
where
intMax = fromIntegral (maxBound :: Int)
intBits = finiteBitSize (0 :: Int)

go :: Natural -> IO Natural
go h
| h <= intMax = fmap fromIntegral (randomRIO (0, fromIntegral h) :: IO Int)
| otherwise = do
x <- fmap fromIntegral (randomRIO (0, maxBound) :: IO Int)
y <- go (shiftR h intBits)
pure (x + shiftL y intBits)
27 changes: 27 additions & 0 deletions clash-vexriscv/tests/unittests/Tests/VexRiscv/Random.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
-- SPDX-FileCopyrightText: 2024 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0
module Tests.VexRiscv.Random where

import Clash.Prelude

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
]

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))
2 changes: 2 additions & 0 deletions clash-vexriscv/tests/unittests/main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down

0 comments on commit 05ec8b0

Please sign in to comment.