Skip to content

Commit bbed638

Browse files
committed
Refactor I2C core and unittest
1 parent 12c3fb6 commit bbed638

File tree

5 files changed

+79
-55
lines changed

5 files changed

+79
-55
lines changed

clash-cores/src/Clash/Cores/I2C/BitMaster.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -70,13 +70,13 @@ bitMaster = exposeClockResetEnable (mealyB bitMasterT bitMasterInit)
7070

7171
bitMasterInit :: BitMasterS
7272
bitMasterInit = BitS { _stateMachine = stateMachineStart
73-
, _busState = busStartState
74-
, _dout = high -- dout register
75-
, _dsclOen = False -- delayed sclOen signal
76-
, _clkEn = True -- statemachine clock enable
77-
, _slaveWait = False -- clock generation signal
78-
, _cnt = 0 -- clock divider counter (synthesis)
79-
}
73+
, _busState = busStartState
74+
, _dout = high -- dout register
75+
, _dsclOen = False -- delayed sclOen signal
76+
, _clkEn = True -- statemachine clock enable
77+
, _slaveWait = False -- clock generation signal
78+
, _cnt = 0 -- clock divider counter (synthesis)
79+
}
8080

8181

8282
bitMasterT :: BitMasterS -> BitMasterI -> (BitMasterS, BitMasterO)

clash-cores/src/Clash/Cores/I2C/ByteMaster.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ byteMasterT s@(ByteS {_srState = ShiftRegister {..}, ..})
138138

139139
(Read, _) -> when coreAck $ do
140140
shiftsr .= True
141-
coreTxd .= (bitCoerce $ not ackRead)
141+
coreTxd .= bitCoerce (not ackRead)
142142
if cntDone then do
143143
byteStateM .= Ack
144144
coreCmd .= I2Cwrite
@@ -156,7 +156,7 @@ byteMasterT s@(ByteS {_srState = ShiftRegister {..}, ..})
156156
byteStateM .= Stop
157157
coreCmd .= I2Cstop
158158
else
159-
coreTxd .= (bitCoerce $ not ackRead)
159+
coreTxd .= bitCoerce (not ackRead)
160160

161161
(Stop, _) -> when coreAck $ do
162162
byteStateM .= Idle
@@ -166,6 +166,6 @@ byteMasterT s@(ByteS {_srState = ShiftRegister {..}, ..})
166166
bitCtrl = (_coreCmd,_coreTxd)
167167
i2cOpAck = (_byteStateM == Ack) && coreAck
168168
ackWrite = i2cOpAck && not (bitCoerce coreRxd)
169-
outp = (i2cOpAck,ackWrite,v2bv dout,bitCtrl)
169+
outp = (i2cOpAck,ackWrite,v2bv dout,bitCtrl)
170170

171171
return outp

clash-cores/test/Test/Cores/I2C.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -15,13 +15,12 @@ import Test.Tasty.HUnit
1515

1616

1717
system0 :: Clock System -> Reset System -> Signal System (Vec 16 (Unsigned 8), Bool, Bool)
18-
system0 clk arst = bundle (registerFile,done,fault)
18+
system0 clk arst = bundle (registerFile,i2cDone <$> confO,i2cFault <$> confO)
1919
where
2020
(_dout,hostAck,_busy,al,ackOut,i2cO) =
21-
i2c clk arst rst (pure True) (pure 19) claim i2cOp (pure True) i2cI
21+
i2c clk arst rst (pure True) (pure 19) (i2cClaim <$> confO) (i2cOp <$> confO) (pure True) i2cI
2222

23-
(claim,i2cOp,done,fault) =
24-
unbundle $ config clk (bundle (rst,fmap not rst,hostAck,ackOut,al))
23+
confO = config clk $ ConfI <$> rst <*> fmap not rst <*> hostAck <*> ackOut <*> al
2524

2625
(sclOut,sdaOut) = unbundle i2cO
2726
scl = fmap (bitCoerce . isNothing) sclOut
@@ -44,8 +43,9 @@ systemResult :: (Vec 16 (Unsigned 8), Bool, Bool)
4443
systemResult = L.last (sampleN 200050 system)
4544

4645
i2cTest :: TestTree
47-
i2cTest = testCase "i2c core testcase passed"
48-
$ assertBool "i2c core test procedure failed" (not fault)
46+
i2cTest =
47+
testCase "I2C" $
48+
assertBool "I2C core test procedure failed" (not fault)
4949
where
5050
fault =
5151
any (\(_,_,f) -> f) (takeWhile (\ (_, done, _) -> not done) $ sample system)

clash-cores/test/Test/Cores/I2C/Config.hs

Lines changed: 19 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,10 @@ import Numeric (showHex)
99
import Clash.Cores.I2C.ByteMaster (I2COperation(..))
1010

1111
data ConfStateMachine = CONFena |
12-
CONFaddr | CONFaddrAck |
13-
CONFreg | CONFregAck |
14-
CONFdata | CONFdataAck |
15-
CONFstop
12+
CONFaddr | CONFaddrAck |
13+
CONFreg | CONFregAck |
14+
CONFdata | CONFdataAck |
15+
CONFstop
1616
deriving Show
1717

1818
data ConfS = ConfS { i2cConfStateM :: ConfStateMachine
@@ -22,8 +22,18 @@ data ConfS = ConfS { i2cConfStateM :: ConfStateMachine
2222
, i2cConfFault :: Bool
2323
}
2424

25-
type ConfI = (Bool,Bool,Bool,Bool,Bool)
26-
type ConfO = (Bool,Maybe I2COperation,Bool,Bool)
25+
data ConfI = ConfI { i2cRst :: Bool
26+
, i2cEna :: Bool
27+
, i2cCmdAck :: Bool
28+
, i2cRxAck :: Bool
29+
, i2cAl :: Bool
30+
}
31+
32+
data ConfO = ConfO { i2cClaim :: Bool
33+
, i2cOp :: Maybe I2COperation
34+
, i2cDone :: Bool
35+
, i2cFault :: Bool
36+
}
2737

2838
confInit :: ConfS
2939
confInit = ConfS { i2cConfStateM = CONFena
@@ -37,13 +47,12 @@ configT
3747
:: Reg ConfS
3848
-> ConfI
3949
-> SimIO ConfO
40-
configT s0 (rst,ena,cmdAck,rxAck,al) = do
50+
configT s0 ConfI{i2cRst=rst,i2cEna=ena,i2cCmdAck=cmdAck,i2cRxAck=rxAck,i2cAl=al} = do
4151
s <- readReg s0
42-
let ConfS confStateM claim i2cOp lutIndex fault = s
52+
let ConfS confStateM claim op lutIndex fault = s
4353

4454
let i2cSlvAddr = 0x34 :: BitVector 8
4555

46-
4756
let success = cmdAck && not al
4857
done = lutIndex == 11
4958

@@ -129,7 +138,7 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
129138
_ -> pure s
130139

131140
writeReg s0 sNext
132-
pure (claim,i2cOp,done,fault)
141+
pure $ ConfO claim op done fault
133142

134143
configLut :: Index 16 -> (BitVector 8, BitVector 8)
135144
configLut i

clash-cores/test/Test/Cores/I2C/Slave.hs

Lines changed: 44 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,15 @@ type ACConfTestI = (Bit,Bit)
2222
type ACConfTestO = (Bit,Vec 16 (Unsigned 8))
2323

2424
i2cSlaveInit :: ACConfTestS
25-
i2cSlaveInit = ACCTS (replicate d16 0x0) (replicate d8 0) 0 ATidle high high high 0
25+
i2cSlaveInit = ACCTS { i2cSlaveRegFile = replicate d16 0x0
26+
, i2cSlaveAddr = replicate d8 0
27+
, i2cSlaveCntr = 0
28+
, i2cSlaveAtStateM = ATidle
29+
, i2cSlavePrevSCL = high
30+
, i2cSlavePrevSDA = high
31+
, i2cSlaveSdaOut = high
32+
, i2cSlaveRegAddr = 0
33+
}
2634

2735
i2cSlaveT :: Reg ACConfTestS -> ACConfTestI -> SimIO ACConfTestO
2836
i2cSlaveT s0 (scl,sda) = do
@@ -45,19 +53,24 @@ i2cSlaveT s0 (scl,sda) = do
4553
| cntr == 8 -> if validAddr then do
4654
display "valid addr"
4755
pure s { i2cSlaveAtStateM = ATaddrAck
48-
, i2cSlaveAddr = repeat low
49-
, i2cSlaveCntr = 0 }
56+
, i2cSlaveAddr = repeat low
57+
, i2cSlaveCntr = 0
58+
}
5059
else do
51-
display "invalid addr"
60+
display $ "invalid addr: " <> show addr
5261
pure s { i2cSlaveAtStateM = ATidle
53-
, i2cSlaveAddr = repeat low
54-
, i2cSlaveCntr = 0}
55-
| sclRising -> pure s { i2cSlaveCntr = cntr + 1
56-
, i2cSlaveAddr = addr <<+ sda
57-
, i2cSlaveSdaOut = high }
62+
, i2cSlaveAddr = repeat low
63+
, i2cSlaveCntr = 0
64+
}
65+
| sclRising -> pure s { i2cSlaveAddr = addr <<+ sda
66+
, i2cSlaveCntr = cntr + 1
67+
, i2cSlaveSdaOut = high
68+
}
5869
ATaddrAck
5970
| sclRising -> do display "addrAck"
60-
pure s { i2cSlaveAtStateM = ATreg, i2cSlaveSdaOut = low }
71+
pure s { i2cSlaveAtStateM = ATreg
72+
, i2cSlaveSdaOut = low
73+
}
6174
ATreg
6275
| cntr == 8 -> if validRegAddr then do
6376
display "valid reg addr"
@@ -67,39 +80,41 @@ i2cSlaveT s0 (scl,sda) = do
6780
, i2cSlaveRegAddr = shiftR (bitCoerce addr) 1
6881
}
6982
else do
70-
display "invalid reg addr"
83+
display $ "invalid reg addr: " <> show addr
7184
pure s { i2cSlaveAtStateM = ATidle
72-
, i2cSlaveAddr = repeat low
73-
, i2cSlaveCntr = 0
85+
, i2cSlaveAddr = repeat low
86+
, i2cSlaveCntr = 0
7487
}
75-
| sclRising -> pure s { i2cSlaveCntr = cntr + 1
76-
, i2cSlaveAddr = addr <<+ sda
77-
, i2cSlaveSdaOut = high }
88+
| sclRising -> pure s { i2cSlaveAddr = addr <<+ sda
89+
, i2cSlaveCntr = cntr + 1
90+
, i2cSlaveSdaOut = high
91+
}
7892
ATregAck
7993
| sclRising -> do display "regAck"
80-
pure s { i2cSlaveSdaOut = low
81-
, i2cSlaveAtStateM = ATval
94+
pure s { i2cSlaveAtStateM = ATval
95+
, i2cSlaveSdaOut = low
8296
}
8397
ATval
8498
| cntr == 8 -> do display "val"
8599
pure s { i2cSlaveAtStateM = ATvalAck
86-
, i2cSlaveAddr = repeat low
87-
, i2cSlaveCntr = 0
88-
, i2cSlaveRegFile =
89-
replace regAddr (bitCoerce addr) regFile
90-
}
91-
| sclRising -> pure s { i2cSlaveCntr = cntr + 1
92-
, i2cSlaveAddr = addr <<+ sda
93-
, i2cSlaveSdaOut = high }
100+
, i2cSlaveAddr = repeat low
101+
, i2cSlaveCntr = 0
102+
, i2cSlaveRegFile =
103+
replace regAddr (bitCoerce addr) regFile
104+
}
105+
| sclRising -> pure s { i2cSlaveAddr = addr <<+ sda
106+
, i2cSlaveCntr = cntr + 1
107+
, i2cSlaveSdaOut = high
108+
}
94109
ATvalAck
95110
| sclRising -> do display "valAck"
96-
pure s { i2cSlaveSdaOut = low
97-
, i2cSlaveAtStateM = ATstop
111+
pure s { i2cSlaveAtStateM = ATstop
112+
, i2cSlaveSdaOut = low
98113
}
99114
ATstop
100115
| stopCondition -> do display "stop"
101116
pure s { i2cSlaveAtStateM = ATidle
102-
, i2cSlaveSdaOut = high
117+
, i2cSlaveSdaOut = high
103118
}
104119
_ -> pure s
105120

0 commit comments

Comments
 (0)