Skip to content

Commit f6fd4e1

Browse files
lmbollenhiddemoll
authored andcommitted
Refactor i2c core to be more user friendly
1 parent 2db7d52 commit f6fd4e1

File tree

7 files changed

+153
-111
lines changed

7 files changed

+153
-111
lines changed

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

Lines changed: 55 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,19 @@ import Clash.Cores.I2C.BitMaster
88
import Clash.Cores.I2C.ByteMaster
99
import Clash.Annotations.TH
1010

11-
-- | Core for I2C communication
11+
-- | Core for I2C communication. Returns the output enable signals for SCL en SDA
12+
-- These signals assume that when they are `True`, they pull down SCL and SDA respectively.
13+
-- For 2-wire I2C, you can use BiSignals (`Clash.Signal.Bidirectional.BiSignalIn` and `Clash.Signal.Bidirectional.BiSignalOut`)
14+
-- An example i2c design could look like this:
15+
-- i2cComp clk rst ena sclIn sdaIn = (sclOut, sdaOut)
16+
-- where
17+
-- sclOut = writeToBiSignal sclIn (mux sclOe (pure $ Just 0) (pure Nothing))
18+
-- sdaOut = writeToBiSignal sdaIn (mux sdaOe (pure $ Just 0) (pure Nothing))
19+
-- (sclOe, sdaOe) = unbundle i2cO
20+
-- i2cIn = bundle (readFromBiSignal sclIn, readFromBiSignal sdaIn)
21+
-- (dout,i2cOpAck,busy,al,ackWrite,i2cOut) = i2c clk arst rst ena clkCnt claimBus i2cOp ackRead i2cI
22+
-- ...
23+
1224
i2c ::
1325
forall dom .
1426
KnownDomain dom =>
@@ -22,45 +34,61 @@ i2c ::
2234
"ena" ::: Signal dom Bool ->
2335
-- | Clock divider
2436
"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 ->
33-
-- | Ack signal
34-
"ackIn" ::: Signal dom Bool ->
35-
-- | Input data
36-
"din" ::: Signal dom (BitVector 8) ->
37+
-- | Claim bus signal
38+
"claimBus" ::: Signal dom Bool ->
39+
-- | I2C operation
40+
"i2cOp" ::: Signal dom (Maybe I2COperation) ->
41+
-- | Acknowledge signal to be transmitted from master to slave on read operations
42+
-- True means SDA is low.
43+
"ackRead" ::: Signal dom Bool ->
3744
-- | I2C input signals (SCL, SDA)
3845
"i2c" ::: Signal dom ("scl" ::: Bit, "sda" ::: Bit) ->
3946
-- |
4047
-- 1. Received data
4148
-- 2. Command acknowledgement
4249
-- 3. I2C bus busy
4350
-- 4. Arbitration lost
44-
-- 5. I2C slave acknowledgement
51+
-- 5. Received acknowledge signal from slave to master on write operations.
52+
-- True means SDA is low.
4553
-- 6. Outgoing I2C signals
46-
-- 6.1 SCL
47-
-- 6.2 SCL Output enable`
48-
-- 6.3 SDA
49-
-- 6.4 SDA Output enable
54+
-- 6.1 SCL Tri-state signals, Nothing means pulled high.
55+
-- 6.2 SDA Tri-state signals, Nothing means pulled high.
5056
"" :::
5157
( "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)
58+
, "i2cOpAck" ::: Signal dom Bool
59+
, "busy" ::: Signal dom Bool
60+
, "al" ::: Signal dom Bool
61+
, "ackWrite" ::: Signal dom Bool
62+
, "i2cO" ::: Signal dom ("sclOut" ::: Maybe Bit, "sclOut" ::: Maybe Bit))
63+
i2c clk arst rst ena clkCnt claimBus i2cOp ackRead i2cI =
64+
(dout,i2cOpAck,busy,al,ackWrite,i2cO)
65+
5866
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
67+
(i2cOpAck,ackWrite,dout,bitCtrl)
68+
= byteMaster clk arst enableGen (rst,claimBus,i2cOp,ackRead,bitResp)
69+
(bitResp,busy,i2cO)
70+
= bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
71+
(_cmdAck,al,_dout) = unbundle bitResp
6272
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
6373
{-# CLASH_OPAQUE i2c #-}
6474

75+
i2cTop ::
76+
"clk" ::: Clock System ->
77+
"arst" ::: Reset System ->
78+
"rst" ::: Signal System Bool ->
79+
"ena" ::: Signal System Bool ->
80+
"clkCnt" ::: Signal System (Unsigned 16) ->
81+
"claimBus" ::: Signal System Bool ->
82+
"i2cOp" ::: Signal System (Maybe I2COperation) ->
83+
"ackRead" ::: Signal System Bool ->
84+
"i2cI" ::: Signal System ("scl" ::: Bit, "sda" ::: Bit) ->
85+
"" :::
86+
( "i2cO" ::: Signal System (BitVector 8)
87+
, "i2cOpAck" ::: Signal System Bool
88+
, "busy" ::: Signal System Bool
89+
, "al" ::: Signal System Bool
90+
, "ackWrite" ::: Signal System Bool
91+
, "i2cO" ::: Signal System ("sclOut" ::: Maybe Bit, "sdaOut" ::: Maybe Bit)
92+
)
6593
i2cTop = i2c @System
6694
makeTopEntity 'i2cTop

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

Lines changed: 8 additions & 5 deletions
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,8 @@ 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
126+
i2cO = (if _sclOen then Nothing else Just 0, if _sdaOen then Nothing else Just 0)
127+
outp = ((_cmdAck,_al,_dout),_busy,i2cO)
125128

126129
return outp

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,8 +21,8 @@ data BitStateMachine
2121
-- | Defines the state machine with control and status registers.
2222
data StateMachine
2323
= StateMachine
24-
{ _sclOen :: Bool -- ^ Enables SCL output
25-
, _sdaOen :: Bool -- ^ Enables SDA output
24+
{ _sclOen :: Bool -- ^ Inverted SCL output enable, False pulls the scl low.
25+
, _sdaOen :: Bool -- ^ Inverted SDA output enable, False pulls the sda low.
2626
, _sdaChk :: Bool -- ^ Checks SDA status
2727
, _cmdAck :: Bool -- ^ Acknowledges command completion
2828
, _bitStateM :: BitStateMachine -- ^ Current state of the bit-level state machine
Lines changed: 66 additions & 57 deletions
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 = 0
23+
getWriteData (WriteData d) = d
1824
data ByteMasterS
1925
= ByteS
2026
{ _srState :: ShiftRegister
@@ -23,27 +29,26 @@ 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 signal to be transmitted from master to slave on read operations.
44+
-- True means SDA is low.
45+
-- 5. Bitmaster response
46+
type ByteMasterI = (Bool,Bool,Maybe I2COperation,Bool,BitRespSig)
4347

4448
-- |
45-
-- 1. Acknowledge for I2C controller
46-
-- 2. I2C acknowledgement
49+
-- 1. Acknowledge for `I2COperation`
50+
-- 2. Received acknowledge signal from slave to master on write operations. True
51+
-- means SDA is low.
4752
-- 3. Data output
4853
-- 4 Bitmaster control signals
4954
type ByteMasterO = (Bool,Bool,BitVector 8,BitCtrlSig)
@@ -73,90 +78,94 @@ byteMasterInit
7378
, _coreTxd = low
7479
, _shiftsr = False
7580
, _ld = False
76-
, _hostAck = False
77-
, _ackOut = True
81+
, _i2cOpAck = False
82+
, _slaveAck = True
7883
}
7984

8085
byteMasterT :: ByteMasterS -> ByteMasterI -> (ByteMasterS, ByteMasterO)
8186
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)
87+
(rst,claimBus,maybeI2COp,ackIn,~(coreAck,al,coreRxd)) = swap $ flip runState s $ do
8588

8689
-- assign dOut the output of the shift-register
87-
dout = _sr
90+
let dout = _sr
8891

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

9194
-- state machine
9295
coreTxd .= head dout
9396
shiftsr .= False
9497
ld .= False
95-
hostAck .= False
98+
i2cOpAck .= False
9699

97100
if rst || al then do
98101
coreCmd .= I2Cnop
99102
coreTxd .= low
100103
byteStateM .= Idle
101-
ackOut .= True
102-
else case _byteStateM of
103-
Idle -> when go $ do
104+
slaveAck .= True
105+
else case (_byteStateM, maybeI2COp) of
106+
(Idle, _) -> when claimBus $ do
104107
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
108+
byteStateM .= Start
109+
coreCmd .= I2Cstart
110+
(Active, Just ReadData) -> do
111+
byteStateM .= Read
112+
coreCmd .= I2Cread
113+
(Active, Just (WriteData _)) -> do
118114
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
115+
byteStateM .= Write
116+
coreCmd .= I2Cwrite
117+
(Active ,Nothing) -> do
118+
byteStateM .= Active
119+
coreCmd .= I2Cnop
120+
(Start, Nothing) -> when coreAck $ do
121+
byteStateM .= Active
122+
coreCmd .= I2Cnop
123+
(Start, Just ReadData) -> when coreAck $ do
124+
byteStateM .= Read
125+
coreCmd .= I2Cread
126+
(Start, Just (WriteData _)) -> when coreAck $ do
127+
ld .= True
128+
byteStateM .= Write
129+
coreCmd .= I2Cwrite
130+
(Write, _) -> when coreAck $ do
126131
if cntDone then do
127132
byteStateM .= Ack
128133
coreCmd .= I2Cread
129134
else do
130135
coreCmd .= I2Cwrite
131136
shiftsr .= True
132-
Read -> when coreAck $ do
137+
138+
(Read, _) -> when coreAck $ do
133139
shiftsr .= True
134140
coreTxd .= bitCoerce ackIn
135141
if cntDone then do
136142
byteStateM .= Ack
137143
coreCmd .= I2Cwrite
138144
else do
139145
coreCmd .= I2Cread
140-
Ack -> if coreAck then do
141-
ackOut .= bitCoerce coreRxd
146+
147+
(Ack, _) ->
148+
if coreAck then do
149+
slaveAck .= bitCoerce coreRxd
142150
coreTxd .= high
143151
-- 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
152+
if claimBus then do
153+
byteStateM .= Active
149154
coreCmd .= I2Cnop
150155
-- generate command acknowledge signal
151-
hostAck .= True
156+
i2cOpAck .= True
157+
else do
158+
byteStateM .= Stop
159+
coreCmd .= I2Cstop
152160
else
153161
coreTxd .= bitCoerce ackIn
154-
Stop -> when coreAck $ do
162+
163+
(Stop, _) -> when coreAck $ do
155164
byteStateM .= Idle
156165
coreCmd .= I2Cnop
157-
hostAck .= True
166+
i2cOpAck .= True
158167

159168
let bitCtrl = (_coreCmd,_coreTxd)
160-
outp = (_hostAck,_ackOut,v2bv dout,bitCtrl)
169+
outp = (_i2cOpAck,_slaveAck,v2bv dout,bitCtrl)
161170

162171
return outp

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,5 +15,6 @@ 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 Tri-state signals (SCL, SDA)
19+
-- Since I2C is a protocol with pull ups, Nothing means pulled high.
20+
type I2COut = (Maybe Bit, Maybe Bit)

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

Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -7,24 +7,29 @@ import qualified Data.List as L
77
import Clash.Explicit.Prelude
88
import Clash.Cores.I2C
99

10+
import Data.Maybe
1011
import Test.Cores.I2C.Slave
1112
import Test.Cores.I2C.Config
13+
import Clash.Cores.I2C.ByteMaster (I2COperation(..))
1214

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

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

22-
(_,sclOen,_,sdaOen) = unbundle i2cO
23-
scl = fmap bitCoerce sclOen
26+
(sclOut,sdaOut) = unbundle i2cO
27+
scl = fmap (bitCoerce . isNothing) sclOut
28+
sda = fmap (bitCoerce . isNothing) sdaOut
2429
i2cI = bundle (scl,sdaS)
2530

2631
(sdaS,registerFile) = unbundle
27-
(i2cSlave clk (bundle (scl, bitCoerce <$> sdaOen)))
32+
(i2cSlave clk (bundle (scl, sda)))
2833

2934
rst = liftA2 (<) rstCounter 500
3035
rstCounter = register clk arst enableGen (0 :: Unsigned 18) (rstCounter + 1)

0 commit comments

Comments
 (0)