Skip to content

Commit e1989c6

Browse files
committed
Fix warnings in i2c core.
1 parent 1320ef5 commit e1989c6

File tree

9 files changed

+148
-120
lines changed

9 files changed

+148
-120
lines changed

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

+21-3
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,10 @@
22

33
module Clash.Cores.I2C where
44

5-
import Clash.Prelude
5+
import Clash.Prelude hiding (read)
66

77
import Clash.Cores.I2C.BitMaster
88
import Clash.Cores.I2C.ByteMaster
9-
import Clash.Cores.I2C.Types
109

1110
{-# ANN i2c
1211
(Synthesize
@@ -32,10 +31,29 @@ import Clash.Cores.I2C.Types
3231
, PortProduct "" [PortName "i2cO_clk"]
3332
]
3433
}) #-}
34+
i2c ::
35+
Clock System ->
36+
Reset System ->
37+
Signal System Bool ->
38+
Signal System Bool ->
39+
Signal System (Unsigned 16) ->
40+
Signal System Bool ->
41+
Signal System Bool ->
42+
Signal System Bool ->
43+
Signal System Bool ->
44+
Signal System Bool ->
45+
Signal System (BitVector 8) ->
46+
Signal System (Bit, Bit) ->
47+
( Signal System (BitVector 8)
48+
, Signal System Bool
49+
, Signal System Bool
50+
, Signal System Bool
51+
, Signal System Bool
52+
, Signal System (Bit, Bool, Bit, Bool))
3553
i2c clk arst rst ena clkCnt start stop read write ackIn din i2cI = (dout,hostAck,busy,al,ackOut,i2cO)
3654
where
3755
(hostAck,ackOut,dout,bitCtrl) = byteMaster clk arst enableGen (rst,start,stop,read,write,ackIn,din,bitResp)
3856
(bitResp,busy,i2cO) = bitMaster clk arst enableGen (rst,ena,clkCnt,bitCtrl,i2cI)
39-
(cmdAck,al,dbout) = unbundle bitResp
57+
(_cmdAck,al,_dbout) = unbundle bitResp
4058
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
4159
{-# CLASH_OPAQUE i2c #-}

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

+3-1
Original file line numberDiff line numberDiff line change
@@ -64,6 +64,7 @@ bitMaster = exposeClockResetEnable (mealyB bitMasterT bitMasterInit)
6464
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
6565
{-# CLASH_OPAQUE bitMaster #-}
6666

67+
bitMasterInit :: BitMasterS
6768
bitMasterInit = BitS { _stateMachine = stateMachineStart
6869
, _busState = busStartState
6970
, _dout = high -- dout register
@@ -79,7 +80,8 @@ bitMasterT s@(BitS { _stateMachine = StateMachine {..}
7980
, _busState = BusStatusCtrl {..}
8081
, ..
8182
})
82-
(rst,ena,clkCnt,(cmd,din),i2cI@(sclI,sdaI)) = swap $ flip runState s $ do
83+
(rst,ena,clkCnt,(cmd,din),i2cI@(_sclI,_sdaI)) =
84+
swap $ flip runState s $ do
8385
-- Whenever the slave is not ready it can delay the cycle by pulling SCL low
8486
-- delay scloEn
8587
dsclOen .= _sclOen

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

+7-6
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ data BusStatusCtrl
2727
makeLenses ''BusStatusCtrl
2828

2929
{-# INLINE busStartState #-}
30+
busStartState :: BusStatusCtrl
3031
busStartState
3132
= BusStatusCtrl
3233
{ _sI2C = (high,high) -- synchronized SCL and SDA input
@@ -53,7 +54,7 @@ busStatusCtrl :: Bool
5354
-> Bool
5455
-> Bool
5556
-> State BusStatusCtrl ()
56-
busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM sdaChk sdaOen = do
57+
busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM0 sdaChk0 sdaOen0 = do
5758
BusStatusCtrl {..} <- get
5859

5960
-- capture SCL and SDA
@@ -103,18 +104,18 @@ busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM sdaChk sdaOen = do
103104
-- arbitration lost when:
104105
-- 1) master drives SDA high, but the i2c bus is low
105106
-- 2) stop detected while not requested (detect during 'idle' state)
106-
let masterHighBusLow = sdaChk && sSDA == low && sdaOen
107+
let masterHighBusLow = sdaChk0 && sSDA == low && sdaOen0
107108
if rst then do
108109
cmdStop .= False
109110
al .= False
110111
else do
111112
when clkEn $
112113
cmdStop .= (cmd == I2Cstop)
113-
if bitStateM == Idle then
114+
if bitStateM0 == Idle then
114115
al .= (masterHighBusLow || (_stopCondition && (not _cmdStop)))
115116
else
116117
al .= masterHighBusLow
117118
where
118-
filterT f = (f!!2 .&. f!!1) .|.
119-
(f!!2 .&. f!!0) .|.
120-
(f!!1 .&. f!!0)
119+
filterT f = (f !! (2 :: Integer) .&. f !! (1 :: Integer)) .|.
120+
(f !! (2 :: Integer) .&. f !! (0 :: Integer)) .|.
121+
(f !! (1 :: Integer) .&. f !! (0 :: Integer))

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

+2-1
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ data StateMachine
2929
makeLenses ''StateMachine
3030

3131
{-# INLINE stateMachineStart #-}
32+
stateMachineStart :: StateMachine
3233
stateMachineStart
3334
= StateMachine
3435
{ _sclOen = True
@@ -175,5 +176,5 @@ bitStateMachine rst al clkEn cmd din = do
175176
I2Cstop -> Stop 0
176177
I2Cwrite -> Write 0
177178
I2Cread -> Read 0
178-
otherwise -> Idle
179+
_ -> Idle
179180
sdaChk .= False

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE RecordWildCards #-}
33
module Clash.Cores.I2C.ByteMaster (byteMaster) where
44

5-
import Clash.Prelude
5+
import Clash.Prelude hiding (read)
66

77
import Control.Lens hiding (Index)
88
import Control.Monad

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

+9-6
Original file line numberDiff line numberDiff line change
@@ -16,18 +16,21 @@ data ShiftRegister
1616
makeLenses ''ShiftRegister
1717

1818
{-# INLINE shiftStartState #-}
19+
20+
shiftStartState :: ShiftRegister
1921
shiftStartState
2022
= ShiftRegister
2123
{ _sr = repeat low
2224
, _dcnt = 0
2325
}
2426

25-
shiftRegister :: Bool
26-
-> Bool
27-
-> Bool
28-
-> Vec 8 Bit
29-
-> Bit
30-
-> State ShiftRegister Bool
27+
shiftRegister ::
28+
Bool ->
29+
Bool ->
30+
Bool ->
31+
Vec 8 Bit ->
32+
Bit ->
33+
State ShiftRegister Bool
3134
shiftRegister rst ld shiftsr din coreRxd = do
3235
(ShiftRegister {..}) <- get
3336

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

+10-8
Original file line numberDiff line numberDiff line change
@@ -10,10 +10,10 @@ import Clash.Cores.I2C
1010
import Test.Cores.I2C.Slave
1111
import Test.Cores.I2C.Config
1212

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

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

26-
(sdaS,regFile) = unbundle
26+
(sdaS,registerFile) = unbundle
2727
(i2cSlave clk (bundle (scl, bitCoerce <$> sdaOen)))
2828

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

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

37-
systemResult = L.last (sampleN 200050 system)
38+
testBenchResult :: (Vec 16 (Unsigned 8), Bool, Bool)
39+
testBenchResult = L.last (sampleN 200050 testBench)

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

+50-50
Original file line numberDiff line numberDiff line change
@@ -12,26 +12,26 @@ data ConfStateMachine = CONFena |
1212
CONFstop
1313
deriving Show
1414

15-
data ConfS = ConfS { confStateM :: ConfStateMachine
16-
, start :: Bool
17-
, stop :: Bool
18-
, write :: Bool
19-
, din :: Vec 8 Bit
20-
, lutIndex :: Index 16
21-
, fault :: Bool
15+
data ConfS = ConfS { i2cConfStateM :: ConfStateMachine
16+
, i2cStart :: Bool
17+
, i2cStop :: Bool
18+
, i2cWrite :: Bool
19+
, i2cDin :: Vec 8 Bit
20+
, i2cLutIndex :: Index 16
21+
, i2cFault :: Bool
2222
}
2323

2424
type ConfI = (Bool,Bool,Bool,Bool,Bool)
2525
type ConfO = (Bool,Bool,Bool,BitVector 8,Bool,Bool)
2626

2727
confInit :: ConfS
28-
confInit = ConfS { confStateM = CONFena
29-
, start = False
30-
, stop = False
31-
, write = False
32-
, din = repeat low
33-
, lutIndex = 0
34-
, fault = False
28+
confInit = ConfS { i2cConfStateM = CONFena
29+
, i2cStart = False
30+
, i2cStop = False
31+
, i2cWrite = False
32+
, i2cDin = repeat low
33+
, i2cLutIndex = 0
34+
, i2cFault = False
3535
}
3636

3737
configT
@@ -53,84 +53,84 @@ configT s0 (rst,ena,cmdAck,rxAck,al) = do
5353
sNext <- if rst then pure confInit else case confStateM of
5454
CONFena
5555
| ena && not done
56-
-> pure s { confStateM = CONFaddr }
56+
-> pure s { i2cConfStateM = CONFaddr }
5757
| done
5858
-> do display "done"
5959
finish 0
6060

6161
CONFaddr
62-
-> pure s { confStateM = CONFaddrAck
63-
, start = True
64-
, write = True
65-
, din = unpack i2cSlvAddr
62+
-> pure s { i2cConfStateM = CONFaddrAck
63+
, i2cStart = True
64+
, i2cWrite = True
65+
, i2cDin = unpack i2cSlvAddr
6666
}
6767

6868
CONFaddrAck
6969
| success
7070
-> do display "CONFaddrAck"
71-
pure s { confStateM = CONFreg
72-
, start = False
73-
, write = False
71+
pure s { i2cConfStateM = CONFreg
72+
, i2cStart = False
73+
, i2cWrite = False
7474
}
7575

7676
CONFreg
7777
-> if rxAck == False then do
7878
display "Success CONFreg"
79-
pure s { confStateM = CONFregAck
80-
, write = True
81-
, din = unpack (fst lutData)
82-
, fault = False
79+
pure s { i2cConfStateM = CONFregAck
80+
, i2cWrite = True
81+
, i2cDin = unpack (fst lutData)
82+
, i2cFault = False
8383
}
8484
else do
8585
display "Failure CONFreg"
86-
finish 1
87-
pure s { confStateM = CONFena
88-
, fault = True
86+
_ <- finish 1
87+
pure s { i2cConfStateM = CONFena
88+
, i2cFault = True
8989
}
9090

9191
CONFregAck
9292
| success
9393
-> do display "CONFregAck"
94-
pure s { confStateM = CONFdata
95-
, write = False
94+
pure s { i2cConfStateM = CONFdata
95+
, i2cWrite = False
9696
}
9797

9898
CONFdata
99-
-> if rxAck == False then do
99+
-> if not rxAck then do
100100
display "Success CONFdata"
101-
pure s { confStateM = CONFdataAck
102-
, write = True
103-
, stop = True
104-
, din = unpack (snd lutData)
105-
, fault = False
101+
pure s { i2cConfStateM = CONFdataAck
102+
, i2cWrite = True
103+
, i2cStop = True
104+
, i2cDin = unpack (snd lutData)
105+
, i2cFault = False
106106
}
107107
else do
108108
display "Failure CONFdata"
109-
finish 1
110-
pure s { confStateM = CONFena
111-
, fault = True
109+
_ <- finish 1
110+
pure s { i2cConfStateM = CONFena
111+
, i2cFault = True
112112
}
113113

114114
CONFdataAck
115115
| success
116116
-> do display "CONFdataAck"
117-
pure s { confStateM = CONFstop
118-
, stop = False
119-
, write = False
117+
pure s { i2cConfStateM = CONFstop
118+
, i2cStop = False
119+
, i2cWrite = False
120120
}
121121

122122
CONFstop
123-
-> if rxAck == False then do
123+
-> if not rxAck then do
124124
display "Success CONFstop"
125-
pure s { confStateM = CONFena
126-
, lutIndex = lutIndex + 1
127-
, fault = False
125+
pure s { i2cConfStateM = CONFena
126+
, i2cLutIndex = lutIndex + 1
127+
, i2cFault = False
128128
}
129129
else do
130130
display "Failure CONFdata"
131-
finish 1
132-
pure s { confStateM = CONFena
133-
, fault = True
131+
_ <- finish 1
132+
pure s { i2cConfStateM = CONFena
133+
, i2cFault = True
134134
}
135135

136136
_ -> pure s

0 commit comments

Comments
 (0)