Skip to content

Commit

Permalink
Refactor i2c core to be more user friendly
Browse files Browse the repository at this point in the history
  • Loading branch information
lmbollen committed Oct 26, 2023
1 parent f08ba82 commit 85d1429
Show file tree
Hide file tree
Showing 4 changed files with 79 additions and 74 deletions.
30 changes: 12 additions & 18 deletions clash-cores/src/Clash/Cores/I2C.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,18 +22,12 @@ i2c ::
"ena" ::: Signal dom Bool ->
-- | Clock divider
"clkCnt" ::: Signal dom (Unsigned 16) ->
-- | Start signal
"start" ::: Signal dom Bool ->
-- | Stop signal
"stop" ::: Signal dom Bool ->
-- | Read signal
"read" ::: Signal dom Bool ->
-- | Write signal
"write" ::: Signal dom Bool ->
-- | Claim bus signal
"claimBus" ::: Signal dom Bool ->
-- | I2C operation
"i2cOp" ::: Signal dom (Maybe I2COperation) ->
-- | Ack signal
"ackIn" ::: Signal dom Bool ->
-- | Input data
"din" ::: Signal dom (BitVector 8) ->
-- | I2C input signals (SCL, SDA)
"i2c" ::: Signal dom ("scl" ::: Bit, "sda" ::: Bit) ->
-- |
Expand All @@ -49,16 +43,16 @@ i2c ::
-- 6.4 SDA Output enable
"" :::
( "i2cO" ::: Signal dom (BitVector 8)
, "scl" ::: Signal dom Bool
, "sclOEn" ::: Signal dom Bool
, "sda" ::: Signal dom Bool
, "sdaOEn" ::: Signal dom Bool
, "i2cOpAck" ::: Signal dom Bool
, "busy" ::: Signal dom Bool
, "al" ::: Signal dom Bool
, "slaveAck" ::: Signal dom Bool
, "i2cO" ::: Signal dom ("scl" ::: Bit, "sclOEn" ::: Bool, "sda" ::: Bit, "sdaOEn" ::: Bool))
i2c clk arst rst ena clkCnt start stop read write ackIn din i2cI = (dout,hostAck,busy,al,ackOut,i2cO)
i2c clk arst rst ena clkCnt claimBus i2cOp ackIn i2cI = (dout,i2cOpAck,busy,al,slaveAck,i2cO)
where
(hostAck,ackOut,dout,bitCtrl) = byteMaster clk arst enableGen (rst,start,stop,read,write,ackIn,din,bitResp)
(bitResp,busy,i2cO) = bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
(_cmdAck,al,_dbout) = unbundle bitResp
(i2cOpAck,slaveAck,dout,bitCtrl) = byteMaster clk arst enableGen (rst,claimBus, i2cOp, ackIn,bitResp)
(bitResp,busy,i2cO) = bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
(_cmdAck,al,_dbout) = unbundle bitResp
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE i2c #-}

Expand Down
6 changes: 5 additions & 1 deletion clash-cores/src/Clash/Cores/I2C/BitMaster.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,11 @@ type BitMasterI = (Bool,Bool,Unsigned 16,BitCtrlSig,I2CIn)
-- 3. Contains the SCL and SDA output signals
type BitMasterO = (BitRespSig,Bool,I2COut)


-- | Bit level I2C controller that contains a statemachine to properly:
-- * Monitor the bus for activity and arbitration.
-- * Read singular bits from the bus.
-- * Write singular bits to the bus.
-- * Return bits read from the bus.
bitMaster
:: KnownDomain dom
=> Clock dom
Expand Down
116 changes: 61 additions & 55 deletions clash-cores/src/Clash/Cores/I2C/ByteMaster.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
module Clash.Cores.I2C.ByteMaster (byteMaster) where
module Clash.Cores.I2C.ByteMaster (byteMaster, I2COperation(..)) where

import Clash.Prelude hiding (read)

Expand All @@ -11,10 +11,15 @@ import Data.Tuple

import Clash.Cores.I2C.ByteMaster.ShiftRegister
import Clash.Cores.I2C.Types
import Data.Maybe (fromJust)

data ByteStateMachine = Idle | Start | Read | Write | Ack | Stop
data ByteStateMachine = Idle | Active | Start | Read | Write | Ack | Stop
deriving (Show, Generic, NFDataX)

data I2COperation = ReadData | WriteData (BitVector 8)
getWriteData :: I2COperation -> BitVector 8
getWriteData ReadData = deepErrorX "Write data undefined for ReadData in I2COperation"
getWriteData (WriteData d) = d
data ByteMasterS
= ByteS
{ _srState :: ShiftRegister
Expand All @@ -23,23 +28,20 @@ data ByteMasterS
, _coreTxd :: Bit -- coreTxd register
, _shiftsr :: Bool -- shift sr
, _ld :: Bool -- load values in to sr
, _hostAck :: Bool -- host cmd acknowlegde register
, _ackOut :: Bool -- slave ack register
, _i2cOpAck :: Bool -- host cmd acknowlegde register
, _slaveAck :: Bool -- slave ack register
}
deriving (Generic, NFDataX)

makeLenses ''ByteMasterS

-- |
-- 1. Statemachine reset
-- 2. Start
-- 3. Stop
-- 4. Read
-- 5. Write
-- 6. Acknowledge
-- 7. Data in
-- 8. Bitmaster response
type ByteMasterI = (Bool,Bool,Bool,Bool,Bool,Bool,BitVector 8,BitRespSig)
-- 2. Claim bus
-- 3. Bus operation
-- 4. Acknowledge
-- 5. Bitmaster response
type ByteMasterI = (Bool,Bool,Maybe I2COperation, Bool,BitRespSig)

-- |
-- 1. Acknowledge for I2C controller
Expand Down Expand Up @@ -73,90 +75,94 @@ byteMasterInit
, _coreTxd = low
, _shiftsr = False
, _ld = False
, _hostAck = False
, _ackOut = True
, _i2cOpAck = False
, _slaveAck = True
}

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

-- assign dOut the output of the shift-register
dout = _sr
let dout = _sr

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

-- state machine
coreTxd .= head dout
shiftsr .= False
ld .= False
hostAck .= False
i2cOpAck .= False

if rst || al then do
coreCmd .= I2Cnop
coreTxd .= low
byteStateM .= Idle
ackOut .= True
else case _byteStateM of
Idle -> when go $ do
slaveAck .= True
else case (_byteStateM, maybeI2COp) of
(Idle, _) -> when claimBus $ do
ld .= True
if start then do
byteStateM .= Start
coreCmd .= I2Cstart
else if read then do
byteStateM .= Read
coreCmd .= I2Cread
else if write then do
byteStateM .= Write
coreCmd .= I2Cwrite
else do-- stop
byteStateM .= Stop
coreCmd .= I2Cstop
Start -> when coreAck $ do
byteStateM .= Start
coreCmd .= I2Cstart
(Active, Just ReadData) -> do
byteStateM .= Read
coreCmd .= I2Cread
(Active, Just (WriteData _)) -> do
byteStateM .= Write
coreCmd .= I2Cwrite
(Active ,Nothing) -> do
byteStateM .= Active
coreCmd .= I2Cnop
(Start, Nothing) -> when coreAck $ do
ld .= True
if read then do
byteStateM .= Read
coreCmd .= I2Cread
else do
byteStateM .= Write
coreCmd .= I2Cwrite
Write -> when coreAck $ do
byteStateM .= Active
coreCmd .= I2Cnop
(Start, Just ReadData) -> when coreAck $ do
ld .= True
byteStateM .= Read
coreCmd .= I2Cread
(Start, Just (WriteData _)) -> when coreAck $ do
byteStateM .= Write
coreCmd .= I2Cwrite
(Write, _) -> when coreAck $ do
if cntDone then do
byteStateM .= Ack
coreCmd .= I2Cread
else do
coreCmd .= I2Cwrite
shiftsr .= True
Read -> when coreAck $ do

(Read, _) -> when coreAck $ do
shiftsr .= True
coreTxd .= bitCoerce ackIn
if cntDone then do
byteStateM .= Ack
coreCmd .= I2Cwrite
else do
coreCmd .= I2Cread
Ack -> if coreAck then do
ackOut .= bitCoerce coreRxd

(Ack, _) ->
if coreAck then do
slaveAck .= bitCoerce coreRxd
coreTxd .= high
-- check for stop; Should a STOP command be generated?
if stop then do
byteStateM .= Stop
coreCmd .= I2Cstop
else do
byteStateM .= Idle
if claimBus then do
byteStateM .= Active
coreCmd .= I2Cnop
-- generate command acknowledge signal
hostAck .= True
i2cOpAck .= True
else do
byteStateM .= Stop
coreCmd .= I2Cstop
else
coreTxd .= bitCoerce ackIn
Stop -> when coreAck $ do

(Stop, _) -> when coreAck $ do
byteStateM .= Idle
coreCmd .= I2Cnop
hostAck .= True
i2cOpAck .= True

let bitCtrl = (_coreCmd,_coreTxd)
outp = (_hostAck,_ackOut,v2bv dout,bitCtrl)
outp = (_i2cOpAck,_slaveAck,v2bv dout,bitCtrl)

return outp
1 change: 1 addition & 0 deletions clash-vexrisc
Submodule clash-vexrisc added at b58133

0 comments on commit 85d1429

Please sign in to comment.