Skip to content

Commit

Permalink
Fix warnings in i2c core.
Browse files Browse the repository at this point in the history
  • Loading branch information
lmbollen committed Oct 3, 2023
1 parent 639d7f6 commit 8553ddc
Show file tree
Hide file tree
Showing 9 changed files with 148 additions and 120 deletions.
24 changes: 21 additions & 3 deletions clash-cores/src/Clash/Cores/I2C.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,10 @@

module Clash.Cores.I2C where

import Clash.Prelude
import Clash.Prelude hiding (read)

import Clash.Cores.I2C.BitMaster
import Clash.Cores.I2C.ByteMaster
import Clash.Cores.I2C.Types

{-# ANN i2c
(Synthesize
Expand All @@ -32,10 +31,29 @@ import Clash.Cores.I2C.Types
, PortProduct "" [PortName "i2cO_clk"]
]
}) #-}
i2c ::
Clock System ->
Reset System ->
Signal System Bool ->
Signal System Bool ->
Signal System (Unsigned 16) ->
Signal System Bool ->
Signal System Bool ->
Signal System Bool ->
Signal System Bool ->
Signal System Bool ->
Signal System (BitVector 8) ->
Signal System (Bit, Bit) ->
( Signal System (BitVector 8)
, Signal System Bool
, Signal System Bool
, Signal System Bool
, Signal System Bool
, Signal System (Bit, Bool, Bit, Bool))
i2c clk arst rst ena clkCnt start stop read write ackIn din i2cI = (dout,hostAck,busy,al,ackOut,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
(_cmdAck,al,_dbout) = unbundle bitResp
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE i2c #-}
4 changes: 3 additions & 1 deletion clash-cores/src/Clash/Cores/I2C/BitMaster.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,7 @@ bitMaster = exposeClockResetEnable (mealyB bitMasterT bitMasterInit)
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE bitMaster #-}

bitMasterInit :: BitMasterS
bitMasterInit = BitS { _stateMachine = stateMachineStart
, _busState = busStartState
, _dout = high -- dout register
Expand All @@ -79,7 +80,8 @@ bitMasterT s@(BitS { _stateMachine = StateMachine {..}
, _busState = BusStatusCtrl {..}
, ..
})
(rst,ena,clkCnt,(cmd,din),i2cI@(sclI,sdaI)) = swap $ flip runState s $ do
(rst,ena,clkCnt,(cmd,din),i2cI@(_sclI,_sdaI)) =
swap $ flip runState s $ do
-- Whenever the slave is not ready it can delay the cycle by pulling SCL low
-- delay scloEn
dsclOen .= _sclOen
Expand Down
13 changes: 7 additions & 6 deletions clash-cores/src/Clash/Cores/I2C/BitMaster/BusCtrl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ data BusStatusCtrl
makeLenses ''BusStatusCtrl

{-# INLINE busStartState #-}
busStartState :: BusStatusCtrl
busStartState
= BusStatusCtrl
{ _sI2C = (high,high) -- synchronized SCL and SDA input
Expand All @@ -53,7 +54,7 @@ busStatusCtrl :: Bool
-> Bool
-> Bool
-> State BusStatusCtrl ()
busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM sdaChk sdaOen = do
busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM0 sdaChk0 sdaOen0 = do
BusStatusCtrl {..} <- get

-- capture SCL and SDA
Expand Down Expand Up @@ -103,18 +104,18 @@ busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM sdaChk sdaOen = do
-- arbitration lost when:
-- 1) master drives SDA high, but the i2c bus is low
-- 2) stop detected while not requested (detect during 'idle' state)
let masterHighBusLow = sdaChk && sSDA == low && sdaOen
let masterHighBusLow = sdaChk0 && sSDA == low && sdaOen0
if rst then do
cmdStop .= False
al .= False
else do
when clkEn $
cmdStop .= (cmd == I2Cstop)
if bitStateM == Idle then
if bitStateM0 == Idle then
al .= (masterHighBusLow || (_stopCondition && (not _cmdStop)))
else
al .= masterHighBusLow
where
filterT f = (f!!2 .&. f!!1) .|.
(f!!2 .&. f!!0) .|.
(f!!1 .&. f!!0)
filterT f = (f !! (2 :: Integer) .&. f !! (1 :: Integer)) .|.
(f !! (2 :: Integer) .&. f !! (0 :: Integer)) .|.
(f !! (1 :: Integer) .&. f !! (0 :: Integer))
3 changes: 2 additions & 1 deletion clash-cores/src/Clash/Cores/I2C/BitMaster/StateMachine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ data StateMachine
makeLenses ''StateMachine

{-# INLINE stateMachineStart #-}
stateMachineStart :: StateMachine
stateMachineStart
= StateMachine
{ _sclOen = True
Expand Down Expand Up @@ -175,5 +176,5 @@ bitStateMachine rst al clkEn cmd din = do
I2Cstop -> Stop 0
I2Cwrite -> Write 0
I2Cread -> Read 0
otherwise -> Idle
_ -> Idle
sdaChk .= False
2 changes: 1 addition & 1 deletion clash-cores/src/Clash/Cores/I2C/ByteMaster.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE RecordWildCards #-}
module Clash.Cores.I2C.ByteMaster (byteMaster) where

import Clash.Prelude
import Clash.Prelude hiding (read)

import Control.Lens hiding (Index)
import Control.Monad
Expand Down
15 changes: 9 additions & 6 deletions clash-cores/src/Clash/Cores/I2C/ByteMaster/ShiftRegister.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,18 +16,21 @@ data ShiftRegister
makeLenses ''ShiftRegister

{-# INLINE shiftStartState #-}

shiftStartState :: ShiftRegister
shiftStartState
= ShiftRegister
{ _sr = repeat low
, _dcnt = 0
}

shiftRegister :: Bool
-> Bool
-> Bool
-> Vec 8 Bit
-> Bit
-> State ShiftRegister Bool
shiftRegister ::
Bool ->
Bool ->
Bool ->
Vec 8 Bit ->
Bit ->
State ShiftRegister Bool
shiftRegister rst ld shiftsr din coreRxd = do
(ShiftRegister {..}) <- get

Expand Down
18 changes: 10 additions & 8 deletions clash-cores/test/Test/Cores/I2C.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,10 @@ import Clash.Cores.I2C
import Test.Cores.I2C.Slave
import Test.Cores.I2C.Config

system0 :: Clock System -> Reset System -> Signal System (Vec 16 (Unsigned 8), Bool, Bool)
system0 clk arst = bundle (regFile,done,fault)
testBench0 :: Clock System -> Reset System -> Signal System (Vec 16 (Unsigned 8), Bool, Bool)
testBench0 clk arst = bundle (registerFile,done,fault)
where
(dout,hostAck,busy,al,ackOut,i2cO) =
(_dout,hostAck,_busy,al,ackOut,i2cO) =
i2c clk arst rst (pure True) (pure 19) start stop (pure False) write (pure True) din i2cI

(start,stop,write,din,done,fault) = unbundle $
Expand All @@ -23,15 +23,17 @@ system0 clk arst = bundle (regFile,done,fault)
scl = fmap bitCoerce sclOen
i2cI = bundle (scl,sdaS)

(sdaS,regFile) = unbundle
(sdaS,registerFile) = unbundle
(i2cSlave clk (bundle (scl, bitCoerce <$> sdaOen)))

rst = liftA2 (<) rstCounter 500
rstCounter = register clk arst enableGen (0 :: Unsigned 18) (rstCounter + 1)
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE system0 #-}
{-# CLASH_OPAQUE testBench0 #-}

{-# ANN system Synthesize { t_name = "system", t_inputs = [], t_output = PortName "" } #-}
system = system0 systemClockGen resetGen
{-# ANN testBench Synthesize { t_name = "testBench", t_inputs = [], t_output = PortName "" } #-}
testBench :: Signal System (Vec 16 (Unsigned 8), Bool, Bool)
testBench = testBench0 systemClockGen resetGen

systemResult = L.last (sampleN 200050 system)
testBenchResult :: (Vec 16 (Unsigned 8), Bool, Bool)
testBenchResult = L.last (sampleN 200050 testBench)
100 changes: 50 additions & 50 deletions clash-cores/test/Test/Cores/I2C/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,26 +12,26 @@ data ConfStateMachine = CONFena |
CONFstop
deriving Show

data ConfS = ConfS { confStateM :: ConfStateMachine
, start :: Bool
, stop :: Bool
, write :: Bool
, din :: Vec 8 Bit
, lutIndex :: Index 16
, fault :: Bool
data ConfS = ConfS { i2cConfStateM :: ConfStateMachine
, i2cStart :: Bool
, i2cStop :: Bool
, i2cWrite :: Bool
, i2cDin :: Vec 8 Bit
, i2cLutIndex :: Index 16
, i2cFault :: Bool
}

type ConfI = (Bool,Bool,Bool,Bool,Bool)
type ConfO = (Bool,Bool,Bool,BitVector 8,Bool,Bool)

confInit :: ConfS
confInit = ConfS { confStateM = CONFena
, start = False
, stop = False
, write = False
, din = repeat low
, lutIndex = 0
, fault = False
confInit = ConfS { i2cConfStateM = CONFena
, i2cStart = False
, i2cStop = False
, i2cWrite = False
, i2cDin = repeat low
, i2cLutIndex = 0
, i2cFault = False
}

configT
Expand All @@ -53,84 +53,84 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
sNext <- if rst then pure confInit else case confStateM of
CONFena
| ena && not done
-> pure s { confStateM = CONFaddr }
-> pure s { i2cConfStateM = CONFaddr }
| done
-> do display "done"
finish 0

CONFaddr
-> pure s { confStateM = CONFaddrAck
, start = True
, write = True
, din = unpack i2cSlvAddr
-> pure s { i2cConfStateM = CONFaddrAck
, i2cStart = True
, i2cWrite = True
, i2cDin = unpack i2cSlvAddr
}

CONFaddrAck
| success
-> do display "CONFaddrAck"
pure s { confStateM = CONFreg
, start = False
, write = False
pure s { i2cConfStateM = CONFreg
, i2cStart = False
, i2cWrite = False
}

CONFreg
-> if rxAck == False then do
display "Success CONFreg"
pure s { confStateM = CONFregAck
, write = True
, din = unpack (fst lutData)
, fault = False
pure s { i2cConfStateM = CONFregAck
, i2cWrite = True
, i2cDin = unpack (fst lutData)
, i2cFault = False
}
else do
display "Failure CONFreg"
finish 1
pure s { confStateM = CONFena
, fault = True
_ <- finish 1
pure s { i2cConfStateM = CONFena
, i2cFault = True
}

CONFregAck
| success
-> do display "CONFregAck"
pure s { confStateM = CONFdata
, write = False
pure s { i2cConfStateM = CONFdata
, i2cWrite = False
}

CONFdata
-> if rxAck == False then do
-> if not rxAck then do
display "Success CONFdata"
pure s { confStateM = CONFdataAck
, write = True
, stop = True
, din = unpack (snd lutData)
, fault = False
pure s { i2cConfStateM = CONFdataAck
, i2cWrite = True
, i2cStop = True
, i2cDin = unpack (snd lutData)
, i2cFault = False
}
else do
display "Failure CONFdata"
finish 1
pure s { confStateM = CONFena
, fault = True
_ <- finish 1
pure s { i2cConfStateM = CONFena
, i2cFault = True
}

CONFdataAck
| success
-> do display "CONFdataAck"
pure s { confStateM = CONFstop
, stop = False
, write = False
pure s { i2cConfStateM = CONFstop
, i2cStop = False
, i2cWrite = False
}

CONFstop
-> if rxAck == False then do
-> if not rxAck then do
display "Success CONFstop"
pure s { confStateM = CONFena
, lutIndex = lutIndex + 1
, fault = False
pure s { i2cConfStateM = CONFena
, i2cLutIndex = lutIndex + 1
, i2cFault = False
}
else do
display "Failure CONFdata"
finish 1
pure s { confStateM = CONFena
, fault = True
_ <- finish 1
pure s { i2cConfStateM = CONFena
, i2cFault = True
}

_ -> pure s
Expand Down
Loading

0 comments on commit 8553ddc

Please sign in to comment.