Skip to content

Commit b50299c

Browse files
committed
Extend haddock documentation for I2C core
1 parent d86b33c commit b50299c

File tree

5 files changed

+85
-64
lines changed

5 files changed

+85
-64
lines changed

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

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -21,17 +21,20 @@ import Clash.Cores.I2C.BitMaster
2121
import Clash.Cores.I2C.ByteMaster
2222

2323
-- | Core for I2C communication. Returns the output enable signals for SCL en SDA
24-
-- These signals assume that when they are `True`, they pull down SCL and SDA respectively.
24+
-- These signals assume that when they are `high`, they pull down SCL and SDA respectively.
2525
-- For 2-wire I2C, you can use BiSignals (`Clash.Signal.Bidirectional.BiSignalIn` and `Clash.Signal.Bidirectional.BiSignalOut`)
26-
-- An example i2c design could look like this:
26+
--
27+
-- === __Example__
28+
--
29+
-- @
2730
-- i2cComp clk rst ena sclIn sdaIn = (sclOut, sdaOut)
2831
-- where
2932
-- sclOut = writeToBiSignal sclIn (mux sclOe (pure $ Just 0) (pure Nothing))
3033
-- sdaOut = writeToBiSignal sdaIn (mux sdaOe (pure $ Just 0) (pure Nothing))
3134
-- (sclOe, sdaOe) = unbundle i2cO
3235
-- i2cIn = bundle (readFromBiSignal sclIn, readFromBiSignal sdaIn)
3336
-- (dout,i2cOpAck,busy,al,ackWrite,i2cOut) = i2c clk arst rst ena clkCnt claimBus i2cOp ackRead i2cI
34-
-- ...
37+
-- @
3538

3639
i2c ::
3740
forall dom .

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

Lines changed: 20 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,11 @@
77

88
{-# LANGUAGE CPP #-}
99
{-# LANGUAGE RecordWildCards #-}
10-
module Clash.Cores.I2C.BitMaster (bitMaster) where
10+
module Clash.Cores.I2C.BitMaster
11+
( bitMaster
12+
, BitMasterI
13+
, BitMasterO
14+
) where
1115

1216
import Clash.Prelude
1317

@@ -21,31 +25,23 @@ import Clash.Cores.I2C.BitMaster.StateMachine
2125
import Clash.Cores.I2C.Types
2226

2327
-- | Internal state of the I2C BitMaster.
24-
--
25-
-- It includes the bus status controller, bit-level state machine, and various control signals and counters.
26-
-- The '_busState' manages the overall status of the I2C bus.
27-
-- The '_stateMachine' handles the bit-level I2C operations.
28-
-- The '_dout' holds the data to be sent out on the I2C bus.
29-
-- The '_dsclOen' is a delayed version of the SCL output enable signal.
30-
-- The '_clkEn' enables the clock for the state machine.
31-
-- The '_slaveWait' indicates if the slave is pulling the SCL line low, causing the master to wait.
32-
-- The '_cnt' is a counter used for clock division.
3328
data BitMasterS
3429
= BitS
35-
{ _busState :: BusStatusCtrl
36-
, _stateMachine :: StateMachine
37-
, _dout :: Bit -- dout register
38-
, _dsclOen :: Bool -- delayed sclOen signal
39-
, _clkEn :: Bool -- statemachine clock enable
40-
, _slaveWait :: Bool -- clock generation signal
41-
, _cnt :: Unsigned 16 -- clock divider counter (synthesis)
30+
{ _busState :: BusStatusCtrl -- ^ Manage overall status of the I2C bus.
31+
, _stateMachine :: StateMachine -- ^ Handles the bit-level I2C operations
32+
, _dout :: Bit -- ^ Data to be sent out on the I2C bus
33+
, _dsclOen :: Bool -- ^ Delayed version of the SCL output enable signal
34+
, _clkEn :: Bool -- ^ Enable the clock for the state machine
35+
, _slaveWait :: Bool -- ^ Whether the slave is pulling the SCL line low, causing the master to wait
36+
, _cnt :: Unsigned 16 -- ^ Counter used for clock division
4237
}
4338
deriving (Generic, NFDataX)
4439

4540
makeLenses ''BitMasterS
4641

4742

4843
-- | 5-tuple containing the input interface for the BitMaster.
44+
--
4945
-- 1. Resets the internal state when asserted
5046
-- 2. Enables or disables the BitMaster
5147
-- 3. Used for clock division
@@ -54,12 +50,14 @@ makeLenses ''BitMasterS
5450
type BitMasterI = (Bool,Bool,Unsigned 16,BitCtrlSig,I2CIn)
5551

5652
-- | 3-tuple containing the output interface for the BitMaster.
53+
--
5754
-- 1. Carries command acknowledgment and other flags
5855
-- 2. Indicates if the BitMaster is currently busy
5956
-- 3. Contains the SCL and SDA output signals
6057
type BitMasterO = (BitRespSig,Bool,I2COut)
6158

6259
-- | Bit level I2C controller that contains a statemachine to properly:
60+
--
6361
-- * Monitor the bus for activity and arbitration.
6462
-- * Read singular bits from the bus.
6563
-- * Write singular bits to the bus.
@@ -78,11 +76,11 @@ bitMaster = exposeClockResetEnable (mealyB bitMasterT bitMasterInit)
7876
bitMasterInit :: BitMasterS
7977
bitMasterInit = BitS { _stateMachine = stateMachineStart
8078
, _busState = busStartState
81-
, _dout = high -- dout register
82-
, _dsclOen = False -- delayed sclOen signal
83-
, _clkEn = True -- statemachine clock enable
84-
, _slaveWait = False -- clock generation signal
85-
, _cnt = 0 -- clock divider counter (synthesis)
79+
, _dout = high
80+
, _dsclOen = False
81+
, _clkEn = True
82+
, _slaveWait = False
83+
, _cnt = 0
8684
}
8785

8886

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

Lines changed: 46 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,11 @@
77

88
{-# LANGUAGE CPP #-}
99
{-# LANGUAGE RecordWildCards #-}
10-
module Clash.Cores.I2C.BitMaster.BusCtrl where
10+
module Clash.Cores.I2C.BitMaster.BusCtrl
11+
( busStatusCtrl
12+
, BusStatusCtrl(..)
13+
, busStartState
14+
) where
1115

1216
import Clash.Prelude
1317
import Control.Lens
@@ -20,16 +24,16 @@ import Clash.Cores.I2C.Types
2024
-- | Bus status control state.
2125
data BusStatusCtrl
2226
= BusStatusCtrl
23-
{ _sI2C :: I2CIn -- synchronized SCL and SDA
24-
, _dI2C :: I2CIn -- delayed sI2C
25-
, _al :: Bool -- internal arbitration lost signal
26-
, _cI2C :: Vec 2 I2CIn -- capture SCL and SDA
27-
, _fI2C :: Vec 3 I2CIn -- filter input for SCL and SDA
28-
, _filterCnt :: Unsigned 14 -- clock divider for filter
29-
, _startCondition :: Bool -- start detected
30-
, _stopCondition :: Bool -- stop detected
31-
, _busy :: Bool -- internal busy signal
32-
, _cmdStop :: Bool -- STOP command
27+
{ _sI2C :: I2CIn -- ^ Synchronized SCL and SDA
28+
, _dI2C :: I2CIn -- ^ Delayed sI2C
29+
, _al :: Bool -- ^ Internal arbitration lost signal
30+
, _cI2C :: Vec 2 I2CIn -- ^ Capture SCL and SDA
31+
, _fI2C :: Vec 3 I2CIn -- ^ Filter input for SCL and SDA
32+
, _filterCnt :: Unsigned 14 -- ^ Clock divider for filter
33+
, _startCondition :: Bool -- ^ Start detected
34+
, _stopCondition :: Bool -- ^ Stop detected
35+
, _busy :: Bool -- ^ Internal busy signal
36+
, _cmdStop :: Bool -- ^ Stop command
3337
} deriving (Generic, NFDataX)
3438

3539
makeLenses ''BusStatusCtrl
@@ -38,32 +42,43 @@ makeLenses ''BusStatusCtrl
3842
busStartState :: BusStatusCtrl
3943
busStartState
4044
= BusStatusCtrl
41-
{ _sI2C = (high,high) -- synchronized SCL and SDA input
42-
, _dI2C = (high,high) -- delayed sI2C
43-
, _al = False -- internal arbitration lost signal
44-
, _cI2C = repeat (high,high) -- capture SCL and SDA
45-
, _fI2C = repeat (high,high) -- filter input for SCL and SDA
46-
, _filterCnt = 0 -- clock divider for filter
47-
, _startCondition = False -- start detected
48-
, _stopCondition = False -- stop detected
49-
, _busy = False -- internal busy signal
50-
, _cmdStop = False -- STOP command
45+
{ _sI2C = (high,high)
46+
, _dI2C = (high,high)
47+
, _al = False
48+
, _cI2C = repeat (high,high)
49+
, _fI2C = repeat (high,high)
50+
, _filterCnt = 0
51+
, _startCondition = False
52+
, _stopCondition = False
53+
, _busy = False
54+
, _cmdStop = False
5155
}
5256

5357
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
5458
{-# CLASH_OPAQUE busStatusCtrl #-}
5559
-- | Low level bus status controller that monitors the state of the bus and performs
5660
-- glitch filtering. It detects start conditions, stop conditions and arbitration loss.
57-
busStatusCtrl :: Bool
58-
-> Bool
59-
-> Unsigned 16
60-
-> I2CCommand
61-
-> Bool
62-
-> I2CIn
63-
-> BitStateMachine
64-
-> Bool
65-
-> Bool
66-
-> State BusStatusCtrl ()
61+
busStatusCtrl
62+
:: Bool
63+
-- ^ Reset
64+
-> Bool
65+
-- ^ Enable
66+
-> Unsigned 16
67+
-- ^ Clock counter used for clock division
68+
-> I2CCommand
69+
-- ^ I2C command
70+
-> Bool
71+
-- ^ Clock enable
72+
-> I2CIn
73+
-- ^ SCL and SDA
74+
-> BitStateMachine
75+
-- ^ Current state of the bit-level state machine
76+
-> Bool
77+
-- ^ Checks SDA status
78+
-> Bool
79+
-- ^ Inverted SDA output enable, False pulls the sda low.
80+
-> State BusStatusCtrl ()
81+
-- ^ Bus status control state
6782
busStatusCtrl rst ena clkCnt cmd clkEn i2cI bitStateM0 sdaChk0 sdaOen0 = do
6883
BusStatusCtrl {..} <- get
6984

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@
99
{-# LANGUAGE RecordWildCards #-}
1010
module Clash.Cores.I2C.BitMaster.StateMachine where
1111

12-
import Clash.Prelude
12+
import Clash.Prelude hiding (Read)
1313
import Control.Lens hiding (Index)
1414
import Control.Monad
1515
import Control.Monad.State
@@ -18,7 +18,7 @@ import Clash.Cores.I2C.Types
1818

1919
-- | States for bit-level I2C operations.
2020
data BitStateMachine
21-
= Idle -- ^ Idle state
21+
= Idle -- ^ Idle state
2222
| Start (Index 5) -- ^ Start condition state
2323
| Stop (Index 4) -- ^ Stop condition state
2424
| Read (Index 4) -- ^ Read operation state

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

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,12 @@
77

88
{-# LANGUAGE CPP #-}
99
{-# LANGUAGE RecordWildCards #-}
10-
module Clash.Cores.I2C.ByteMaster (byteMaster, I2COperation(..)) where
10+
module Clash.Cores.I2C.ByteMaster
11+
( byteMaster
12+
, ByteMasterI
13+
, ByteMasterO
14+
, I2COperation(..)
15+
) where
1116

1217
import Clash.Prelude
1318

@@ -33,11 +38,11 @@ getWriteData (WriteData d) = d
3338
data ByteMasterS
3439
= ByteS
3540
{ _srState :: ShiftRegister
36-
, _byteStateM :: ByteStateMachine -- State machine
37-
, _coreCmd :: I2CCommand -- coreCmd register
38-
, _coreTxd :: Bit -- coreTxd register
39-
, _shiftsr :: Bool -- shift sr
40-
, _ld :: Bool -- load values in to sr
41+
, _byteStateM :: ByteStateMachine
42+
, _coreCmd :: I2CCommand
43+
, _coreTxd :: Bit
44+
, _shiftsr :: Bool
45+
, _ld :: Bool
4146
}
4247
deriving (Generic, NFDataX, Eq)
4348

0 commit comments

Comments
 (0)