Skip to content

Commit

Permalink
Add I2C unit test to clash-cores:unittests
Browse files Browse the repository at this point in the history
  • Loading branch information
lmbollen committed Oct 31, 2023
1 parent a331846 commit d663a1a
Show file tree
Hide file tree
Showing 4 changed files with 18 additions and 4 deletions.
6 changes: 5 additions & 1 deletion clash-cores/src/Clash/Cores/I2C.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
{-# LANGUAGE CPP #-}

module Clash.Cores.I2C where
module Clash.Cores.I2C
( i2c
, i2cTop
, Clash.Cores.I2C.ByteMaster.I2COperation(..)
) where

import Clash.Prelude hiding (read)

Expand Down
12 changes: 10 additions & 2 deletions clash-cores/test/Test/Cores/I2C.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,11 @@ import Clash.Explicit.Prelude
import Clash.Cores.I2C

import Data.Maybe
import Test.Cores.I2C.Slave
import Test.Cores.I2C.Config
import Clash.Cores.I2C.ByteMaster (I2COperation(..))
import Test.Cores.I2C.Slave
import Test.Tasty
import Test.Tasty.HUnit


system0 :: Clock System -> Reset System -> Signal System (Vec 16 (Unsigned 8), Bool, Bool)
system0 clk arst = bundle (registerFile,done,fault)
Expand Down Expand Up @@ -42,3 +44,9 @@ system = system0 systemClockGen resetGen

systemResult :: (Vec 16 (Unsigned 8), Bool, Bool)
systemResult = L.last (sampleN 200050 system)

i2cTest :: TestTree
i2cTest = testCase "i2c core testcase passed."
$ assertBool "i2c core test procedure failed" (not f)
where
(_, _, f) = L.last $ takeWhile (\ (_, done, _) -> not done) $ sample system
2 changes: 1 addition & 1 deletion clash-cores/test/Test/Cores/I2C/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
-> pure s { i2cConfStateM = CONFaddr }
| done
-> do display "done"
finish 0
pure s

CONFaddr
-> pure s { i2cConfStateM = CONFaddrAck
Expand Down
2 changes: 2 additions & 0 deletions clash-cores/test/unittests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Main where
import Prelude
import Test.Tasty

import qualified Test.Cores.I2C
import qualified Test.Cores.SPI
import qualified Test.Cores.SPI.MultiSlave
import qualified Test.Cores.UART
Expand All @@ -23,6 +24,7 @@ tests = testGroup "Unittests"
, Test.Cores.UART.tests
, Test.Cores.Xilinx.DcFifo.tests
, Test.Cores.Xilinx.BlockRam.tests
, Test.Cores.I2C.i2cTest
]

main :: IO ()
Expand Down

0 comments on commit d663a1a

Please sign in to comment.