Skip to content

Commit a331846

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

File tree

7 files changed

+144
-106
lines changed

7 files changed

+144
-106
lines changed

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

Lines changed: 50 additions & 24 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,slaveAck,i2cOut) = i2c clk arst rst ena clkCnt claimBus i2cOp ackIn i2cI
22+
-- ...
23+
1224
i2c ::
1325
forall dom .
1426
KnownDomain dom =>
@@ -22,18 +34,12 @@ 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 ->
37+
-- | Claim bus signal
38+
"claimBus" ::: Signal dom Bool ->
39+
-- | I2C operation
40+
"i2cOp" ::: Signal dom (Maybe I2COperation) ->
3341
-- | Ack signal
3442
"ackIn" ::: Signal dom Bool ->
35-
-- | Input data
36-
"din" ::: Signal dom (BitVector 8) ->
3743
-- | I2C input signals (SCL, SDA)
3844
"i2c" ::: Signal dom ("scl" ::: Bit, "sda" ::: Bit) ->
3945
-- |
@@ -43,24 +49,44 @@ i2c ::
4349
-- 4. Arbitration lost
4450
-- 5. I2C slave acknowledgement
4551
-- 6. Outgoing I2C signals
46-
-- 6.1 SCL
47-
-- 6.2 SCL Output enable`
48-
-- 6.3 SDA
49-
-- 6.4 SDA Output enable
52+
-- 6.1 SCL Tri-state signals, Nothing means pulled high.
53+
-- 6.2 SDA Tri-state signals, Nothing means pulled high.
5054
"" :::
5155
( "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)
56+
, "i2cOpAck" ::: Signal dom Bool
57+
, "busy" ::: Signal dom Bool
58+
, "al" ::: Signal dom Bool
59+
, "slaveAck" ::: Signal dom Bool
60+
, "i2cO" ::: Signal dom ("sclOut" ::: Maybe Bit, "sclOut" ::: Maybe Bit))
61+
i2c clk arst rst ena clkCnt claimBus i2cOp ackIn i2cI =
62+
(dout,i2cOpAck,busy,al,slaveAck,i2cO)
63+
5864
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
65+
(i2cOpAck,slaveAck,dout,bitCtrl)
66+
= byteMaster clk arst enableGen (rst,claimBus, i2cOp, ackIn,bitResp)
67+
(bitResp,busy,i2cO)
68+
= bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
69+
(_cmdAck,al,_dout) = unbundle bitResp
6270
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
6371
{-# CLASH_OPAQUE i2c #-}
6472

73+
i2cTop ::
74+
"clk" ::: Clock System ->
75+
"arst" ::: Reset System ->
76+
"rst" ::: Signal System Bool ->
77+
"ena" ::: Signal System Bool ->
78+
"clkCnt" ::: Signal System (Unsigned 16) ->
79+
"claimBus" ::: Signal System Bool ->
80+
"i2cOp" ::: Signal System (Maybe I2COperation) ->
81+
"ackIn" ::: Signal System Bool ->
82+
"i2cI" ::: Signal System ("scl" ::: Bit, "sda" ::: Bit) ->
83+
"" :::
84+
( "i2cO" ::: Signal System (BitVector 8)
85+
, "i2cOpAck" ::: Signal System Bool
86+
, "busy" ::: Signal System Bool
87+
, "al" ::: Signal System Bool
88+
, "slaveAck" ::: Signal System Bool
89+
, "i2cO" ::: Signal System ("sclOut" ::: Maybe Bit, "sdaOut" ::: Maybe Bit)
90+
)
6591
i2cTop = i2c @System
6692
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: 62 additions & 55 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,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

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)