Skip to content

Commit 6af2276

Browse files
committed
Refactor i2c core to be more user friendly
1 parent f08ba82 commit 6af2276

File tree

6 files changed

+98
-97
lines changed

6 files changed

+98
-97
lines changed

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

+13-19
Original file line numberDiff line numberDiff line change
@@ -22,18 +22,12 @@ i2c ::
2222
"ena" ::: Signal dom Bool ->
2323
-- | Clock divider
2424
"clkCnt" ::: Signal dom (Unsigned 16) ->
25-
-- | Start signal
26-
"start" ::: Signal dom Bool ->
27-
-- | Stop signal
28-
"stop" ::: Signal dom Bool ->
29-
-- | Read signal
30-
"read" ::: Signal dom Bool ->
31-
-- | Write signal
32-
"write" ::: Signal dom Bool ->
25+
-- | Claim bus signal
26+
"claimBus" ::: Signal dom Bool ->
27+
-- | I2C operation
28+
"i2cOp" ::: Signal dom (Maybe I2COperation) ->
3329
-- | Ack signal
3430
"ackIn" ::: Signal dom Bool ->
35-
-- | Input data
36-
"din" ::: Signal dom (BitVector 8) ->
3731
-- | I2C input signals (SCL, SDA)
3832
"i2c" ::: Signal dom ("scl" ::: Bit, "sda" ::: Bit) ->
3933
-- |
@@ -49,16 +43,16 @@ i2c ::
4943
-- 6.4 SDA Output enable
5044
"" :::
5145
( "i2cO" ::: Signal dom (BitVector 8)
52-
, "scl" ::: Signal dom Bool
53-
, "sclOEn" ::: Signal dom Bool
54-
, "sda" ::: Signal dom Bool
55-
, "sdaOEn" ::: Signal dom Bool
56-
, "i2cO" ::: Signal dom ("scl" ::: Bit, "sclOEn" ::: Bool, "sda" ::: Bit, "sdaOEn" ::: Bool))
57-
i2c clk arst rst ena clkCnt start stop read write ackIn din i2cI = (dout,hostAck,busy,al,ackOut,i2cO)
46+
, "i2cOpAck" ::: Signal dom Bool
47+
, "busy" ::: Signal dom Bool
48+
, "al" ::: Signal dom Bool
49+
, "slaveAck" ::: Signal dom Bool
50+
, "i2cO" ::: Signal dom ("sclOEn" ::: Bool, "sdaOEn" ::: Bool))
51+
i2c clk arst rst ena clkCnt claimBus i2cOp ackIn i2cI = (dout,i2cOpAck,busy,al,slaveAck,i2cO)
5852
where
59-
(hostAck,ackOut,dout,bitCtrl) = byteMaster clk arst enableGen (rst,start,stop,read,write,ackIn,din,bitResp)
60-
(bitResp,busy,i2cO) = bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
61-
(_cmdAck,al,_dbout) = unbundle bitResp
53+
(i2cOpAck,slaveAck,dout,bitCtrl) = byteMaster clk arst enableGen (rst,claimBus, i2cOp, ackIn,bitResp)
54+
(bitResp,busy,i2cO) = bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
55+
(_cmdAck,al,_dbout) = unbundle bitResp
6256
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
6357
{-# CLASH_OPAQUE i2c #-}
6458

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

+6-5
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,11 @@ type BitMasterI = (Bool,Bool,Unsigned 16,BitCtrlSig,I2CIn)
5252
-- 3. Contains the SCL and SDA output signals
5353
type BitMasterO = (BitRespSig,Bool,I2COut)
5454

55-
55+
-- | Bit level I2C controller that contains a statemachine to properly:
56+
-- * Monitor the bus for activity and arbitration.
57+
-- * Read singular bits from the bus.
58+
-- * Write singular bits to the bus.
59+
-- * Return bits read from the bus.
5660
bitMaster
5761
:: KnownDomain dom
5862
=> Clock dom
@@ -118,9 +122,6 @@ bitMasterT s@(BitS { _stateMachine = StateMachine {..}
118122
zoom stateMachine (bitStateMachine rst _al _clkEn cmd din)
119123

120124
-- assign outputs
121-
let sclO = low
122-
sdaO = low
123-
i2cO = (sclO,_sclOen,sdaO,_sdaOen)
124-
outp = ((_cmdAck,_al,_dout),_busy,i2cO)
125+
let outp = ((_cmdAck,_al,_dout),_busy,(_sclOen,_sdaOen))
125126

126127
return outp
+62-55
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE RecordWildCards #-}
3-
module Clash.Cores.I2C.ByteMaster (byteMaster) where
3+
module Clash.Cores.I2C.ByteMaster (byteMaster, I2COperation(..)) where
44

55
import Clash.Prelude hiding (read)
66

@@ -11,10 +11,16 @@ import Data.Tuple
1111

1212
import Clash.Cores.I2C.ByteMaster.ShiftRegister
1313
import Clash.Cores.I2C.Types
14+
import Data.Maybe (fromJust)
1415

15-
data ByteStateMachine = Idle | Start | Read | Write | Ack | Stop
16+
data ByteStateMachine = Idle | Active | Start | Read | Write | Ack | Stop
1617
deriving (Show, Generic, NFDataX)
1718

19+
data I2COperation = ReadData | WriteData (BitVector 8)
20+
deriving (Generic, NFDataX)
21+
getWriteData :: I2COperation -> BitVector 8
22+
getWriteData ReadData = deepErrorX "Write data undefined for ReadData in I2COperation"
23+
getWriteData (WriteData d) = d
1824
data ByteMasterS
1925
= ByteS
2026
{ _srState :: ShiftRegister
@@ -23,23 +29,20 @@ data ByteMasterS
2329
, _coreTxd :: Bit -- coreTxd register
2430
, _shiftsr :: Bool -- shift sr
2531
, _ld :: Bool -- load values in to sr
26-
, _hostAck :: Bool -- host cmd acknowlegde register
27-
, _ackOut :: Bool -- slave ack register
32+
, _i2cOpAck :: Bool -- host cmd acknowlegde register
33+
, _slaveAck :: Bool -- slave ack register
2834
}
2935
deriving (Generic, NFDataX)
3036

3137
makeLenses ''ByteMasterS
3238

3339
-- |
3440
-- 1. Statemachine reset
35-
-- 2. Start
36-
-- 3. Stop
37-
-- 4. Read
38-
-- 5. Write
39-
-- 6. Acknowledge
40-
-- 7. Data in
41-
-- 8. Bitmaster response
42-
type ByteMasterI = (Bool,Bool,Bool,Bool,Bool,Bool,BitVector 8,BitRespSig)
41+
-- 2. Claim bus
42+
-- 3. Bus operation
43+
-- 4. Acknowledge
44+
-- 5. Bitmaster response
45+
type ByteMasterI = (Bool,Bool,Maybe I2COperation, Bool,BitRespSig)
4346

4447
-- |
4548
-- 1. Acknowledge for I2C controller
@@ -73,90 +76,94 @@ byteMasterInit
7376
, _coreTxd = low
7477
, _shiftsr = False
7578
, _ld = False
76-
, _hostAck = False
77-
, _ackOut = True
79+
, _i2cOpAck = False
80+
, _slaveAck = True
7881
}
7982

8083
byteMasterT :: ByteMasterS -> ByteMasterI -> (ByteMasterS, ByteMasterO)
8184
byteMasterT s@(ByteS {_srState = ShiftRegister {..}, ..})
82-
(rst,start,stop,read,write,ackIn,din,~(coreAck,al,coreRxd)) = swap $ flip runState s $ do
83-
-- generate go-signal
84-
let go = (read || write || stop) && (not _hostAck)
85+
(rst,claimBus,maybeI2COp,ackIn,~(coreAck,al,coreRxd)) = swap $ flip runState s $ do
8586

8687
-- assign dOut the output of the shift-register
87-
dout = _sr
88+
let dout = _sr
8889

89-
cntDone <- zoom srState (shiftRegister rst _ld _shiftsr (bv2v din) coreRxd)
90+
cntDone <- zoom srState (shiftRegister rst _ld _shiftsr (bv2v (getWriteData $ fromJust maybeI2COp )) coreRxd)
9091

9192
-- state machine
9293
coreTxd .= head dout
9394
shiftsr .= False
9495
ld .= False
95-
hostAck .= False
96+
i2cOpAck .= False
9697

9798
if rst || al then do
9899
coreCmd .= I2Cnop
99100
coreTxd .= low
100101
byteStateM .= Idle
101-
ackOut .= True
102-
else case _byteStateM of
103-
Idle -> when go $ do
102+
slaveAck .= True
103+
else case (_byteStateM, maybeI2COp) of
104+
(Idle, _) -> when claimBus $ do
104105
ld .= True
105-
if start then do
106-
byteStateM .= Start
107-
coreCmd .= I2Cstart
108-
else if read then do
109-
byteStateM .= Read
110-
coreCmd .= I2Cread
111-
else if write then do
112-
byteStateM .= Write
113-
coreCmd .= I2Cwrite
114-
else do-- stop
115-
byteStateM .= Stop
116-
coreCmd .= I2Cstop
117-
Start -> when coreAck $ do
106+
byteStateM .= Start
107+
coreCmd .= I2Cstart
108+
(Active, Just ReadData) -> do
109+
byteStateM .= Read
110+
coreCmd .= I2Cread
111+
(Active, Just (WriteData _)) -> do
118112
ld .= True
119-
if read then do
120-
byteStateM .= Read
121-
coreCmd .= I2Cread
122-
else do
123-
byteStateM .= Write
124-
coreCmd .= I2Cwrite
125-
Write -> when coreAck $ do
113+
byteStateM .= Write
114+
coreCmd .= I2Cwrite
115+
(Active ,Nothing) -> do
116+
byteStateM .= Active
117+
coreCmd .= I2Cnop
118+
(Start, Nothing) -> when coreAck $ do
119+
byteStateM .= Active
120+
coreCmd .= I2Cnop
121+
(Start, Just ReadData) -> when coreAck $ do
122+
byteStateM .= Read
123+
coreCmd .= I2Cread
124+
(Start, Just (WriteData _)) -> when coreAck $ do
125+
ld .= True
126+
byteStateM .= Write
127+
coreCmd .= I2Cwrite
128+
(Write, _) -> when coreAck $ do
126129
if cntDone then do
127130
byteStateM .= Ack
128131
coreCmd .= I2Cread
129132
else do
130133
coreCmd .= I2Cwrite
131134
shiftsr .= True
132-
Read -> when coreAck $ do
135+
136+
(Read, _) -> when coreAck $ do
133137
shiftsr .= True
134138
coreTxd .= bitCoerce ackIn
135139
if cntDone then do
136140
byteStateM .= Ack
137141
coreCmd .= I2Cwrite
138142
else do
139143
coreCmd .= I2Cread
140-
Ack -> if coreAck then do
141-
ackOut .= bitCoerce coreRxd
144+
145+
(Ack, _) ->
146+
if coreAck then do
147+
slaveAck .= bitCoerce coreRxd
142148
coreTxd .= high
143149
-- check for stop; Should a STOP command be generated?
144-
if stop then do
145-
byteStateM .= Stop
146-
coreCmd .= I2Cstop
147-
else do
148-
byteStateM .= Idle
150+
if claimBus then do
151+
byteStateM .= Active
149152
coreCmd .= I2Cnop
150153
-- generate command acknowledge signal
151-
hostAck .= True
154+
i2cOpAck .= True
155+
else do
156+
byteStateM .= Stop
157+
coreCmd .= I2Cstop
152158
else
153159
coreTxd .= bitCoerce ackIn
154-
Stop -> when coreAck $ do
160+
161+
(Stop, _) -> when coreAck $ do
155162
byteStateM .= Idle
156163
coreCmd .= I2Cnop
157-
hostAck .= True
164+
i2cOpAck .= True
158165

159166
let bitCtrl = (_coreCmd,_coreTxd)
160-
outp = (_hostAck,_ackOut,v2bv dout,bitCtrl)
167+
outp = (_i2cOpAck,_slaveAck,v2bv dout,bitCtrl)
161168

162169
return outp

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

+2-2
Original file line numberDiff line numberDiff line change
@@ -15,5 +15,5 @@ type BitRespSig = (Bool, Bool, Bit)
1515
-- | I2C input signals (SCL, SDA).
1616
type I2CIn = (Bit, Bit)
1717

18-
-- | I2C output signals (SCL, SCL enable, SDA, SDA enable).
19-
type I2COut = (Bit, Bool, Bit, Bool)
18+
-- | I2C output signals (SCL enable, SDA enable).
19+
type I2COut = (Bool, Bool)

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

+6-3
Original file line numberDiff line numberDiff line change
@@ -9,17 +9,20 @@ import Clash.Cores.I2C
99

1010
import Test.Cores.I2C.Slave
1111
import Test.Cores.I2C.Config
12+
import Clash.Cores.I2C.ByteMaster (I2COperation(..))
1213

1314
system0 :: Clock System -> Reset System -> Signal System (Vec 16 (Unsigned 8), Bool, Bool)
1415
system0 clk arst = bundle (registerFile,done,fault)
1516
where
1617
(_dout,hostAck,_busy,al,ackOut,i2cO) =
17-
i2c clk arst rst (pure True) (pure 19) start stop (pure False) write (pure True) din i2cI
18+
i2c clk arst rst (pure True) (pure 19) claim i2cOp (pure True) i2cI
1819

19-
(start,stop,write,din,done,fault) = unbundle $
20+
i2cOp = mux claim (Just <$> mux write (WriteData <$> din) (pure ReadData)) (pure Nothing)
21+
22+
(claim,write,din,done,fault) = unbundle $
2023
config clk (bundle (rst, fmap not rst,hostAck,ackOut,al))
2124

22-
(_,sclOen,_,sdaOen) = unbundle i2cO
25+
(sclOen,sdaOen) = unbundle i2cO
2326
scl = fmap bitCoerce sclOen
2427
i2cI = bundle (scl,sdaS)
2528

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

+9-13
Original file line numberDiff line numberDiff line change
@@ -13,21 +13,19 @@ data ConfStateMachine = CONFena |
1313
deriving Show
1414

1515
data ConfS = ConfS { i2cConfStateM :: ConfStateMachine
16-
, i2cStart :: Bool
17-
, i2cStop :: Bool
16+
, i2cClaim :: Bool
1817
, i2cWrite :: Bool
1918
, i2cDin :: Vec 8 Bit
2019
, i2cLutIndex :: Index 16
2120
, i2cFault :: Bool
2221
}
2322

2423
type ConfI = (Bool,Bool,Bool,Bool,Bool)
25-
type ConfO = (Bool,Bool,Bool,BitVector 8,Bool,Bool)
24+
type ConfO = (Bool,Bool,BitVector 8,Bool,Bool)
2625

2726
confInit :: ConfS
2827
confInit = ConfS { i2cConfStateM = CONFena
29-
, i2cStart = False
30-
, i2cStop = False
28+
, i2cClaim = False
3129
, i2cWrite = False
3230
, i2cDin = repeat low
3331
, i2cLutIndex = 0
@@ -40,7 +38,7 @@ configT
4038
-> SimIO ConfO
4139
configT s0 (rst,ena,cmdAck,rxAck,al) = do
4240
s <- readReg s0
43-
let ConfS confStateM start stop write din lutIndex fault = s
41+
let ConfS confStateM claim write din lutIndex fault = s
4442

4543
let i2cSlvAddr = 0x34 :: BitVector 8
4644

@@ -60,7 +58,7 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
6058

6159
CONFaddr
6260
-> pure s { i2cConfStateM = CONFaddrAck
63-
, i2cStart = True
61+
, i2cClaim = True
6462
, i2cWrite = True
6563
, i2cDin = unpack i2cSlvAddr
6664
}
@@ -69,12 +67,11 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
6967
| success
7068
-> do display "CONFaddrAck"
7169
pure s { i2cConfStateM = CONFreg
72-
, i2cStart = False
7370
, i2cWrite = False
7471
}
7572

7673
CONFreg
77-
-> if rxAck == False then do
74+
-> if not rxAck then do
7875
display "Success CONFreg"
7976
pure s { i2cConfStateM = CONFregAck
8077
, i2cWrite = True
@@ -100,7 +97,7 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
10097
display "Success CONFdata"
10198
pure s { i2cConfStateM = CONFdataAck
10299
, i2cWrite = True
103-
, i2cStop = True
100+
, i2cClaim = False
104101
, i2cDin = unpack (snd lutData)
105102
, i2cFault = False
106103
}
@@ -115,7 +112,6 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
115112
| success
116113
-> do display "CONFdataAck"
117114
pure s { i2cConfStateM = CONFstop
118-
, i2cStop = False
119115
, i2cWrite = False
120116
}
121117

@@ -127,7 +123,7 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
127123
, i2cFault = False
128124
}
129125
else do
130-
display "Failure CONFdata"
126+
display "Failure CONFstop"
131127
_ <- finish 1
132128
pure s { i2cConfStateM = CONFena
133129
, i2cFault = True
@@ -136,7 +132,7 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
136132
_ -> pure s
137133

138134
writeReg s0 sNext
139-
pure (start,stop,write,pack din,done,fault)
135+
pure (claim,write,pack din,done,fault)
140136

141137
configLut :: Index 16 -> (BitVector 8, BitVector 8)
142138
configLut i

0 commit comments

Comments
 (0)