Skip to content

Commit aaf2626

Browse files
committed
SPI: Generalize to multi-lane MISO/MISO
It is fairly common for single SPI bus to consist of a set of parallel MISO/MOSI lanes (c.f. QSPI FLASH). For instance: * many multi-channel ADCs allow each converter to clock out over its own MISO lane to reduce the clockrate needed to achieve the designed conversion rate. * similarly, QSPI FLASH relies upon four bidirectional outputs to increase data rate. Here we extend Clash.Cores.SPI to facilitate this use-case by introducing `spiMaster'` and `spiSlave'`, which allow arbitrary MISO/MOSI lane widths.
1 parent 4333e2c commit aaf2626

File tree

1 file changed

+114
-38
lines changed
  • clash-cores/src/Clash/Cores

1 file changed

+114
-38
lines changed

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

Lines changed: 114 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,13 @@ module Clash.Cores.SPI
1212
, SpiMasterIn(..)
1313
, SpiMasterOut(..)
1414
, spiMaster
15+
, spiMaster1
1516
-- * SPI slave
1617
, SpiSlaveIn(..)
1718
, SpiSlaveOut(..)
1819
, SPISlaveConfig(..)
1920
, spiSlave
21+
, spiSlave1
2022
-- ** Vendor configured SPI slaves
2123
, spiSlaveLatticeSBIO
2224
, spiSlaveLatticeBB
@@ -125,7 +127,7 @@ sampleOnLeading _ = False
125127
sampleOnTrailing :: SPIMode -> Bool
126128
sampleOnTrailing = not . sampleOnLeading
127129

128-
data SPISlaveConfig ds dom
130+
data SPISlaveConfig ds dom (misoW :: Nat) (mosiW :: Nat)
129131
= SPISlaveConfig
130132
{ spiSlaveConfigMode :: SPIMode
131133
-- ^ SPI mode
@@ -139,30 +141,34 @@ data SPISlaveConfig ds dom
139141
--
140142
-- * Set to /False/ when core clock is twice as fast, or as fast, as the SCK
141143
, spiSlaveConfigBuffer
142-
:: BiSignalIn ds dom 1
144+
:: BiSignalIn ds dom misoW
143145
-> Signal dom Bool
144-
-> Signal dom Bit
145-
-> BiSignalOut ds dom 1
146+
-> Signal dom (BitVector misoW)
147+
-> BiSignalOut ds dom misoW
146148
-- ^ Tri-state buffer: first argument is the inout pin, second
147149
-- argument is the output enable, third argument is the value to
148150
-- output when the enable is high
149151
}
150152

151153
-- | SPI capture and shift logic that is shared between slave and master
152154
spiCommon
153-
:: forall n dom
154-
. (HiddenClockResetEnable dom, KnownNat n, 1 <= n)
155+
:: forall n dom inW outW
156+
. ( HiddenClockResetEnable dom
157+
, KnownNat inW
158+
, KnownNat outW
159+
, KnownNat n
160+
, 1 <= n )
155161
=> SPIMode
156162
-> Signal dom Bool
157163
-- ^ Slave select
158-
-> Signal dom Bit
164+
-> Signal dom (BitVector inW)
159165
-- ^ Slave: MOSI; Master: MISO
160166
-> Signal dom Bool
161167
-- ^ SCK
162-
-> Signal dom (BitVector n)
163-
-> ( Signal dom Bit -- Slave: MISO; Master: MOSI
164-
, Signal dom Bool -- Acknowledge start of transfer
165-
, Signal dom (Maybe (BitVector n))
168+
-> Signal dom (Vec outW (BitVector n))
169+
-> ( Signal dom (BitVector outW) -- Slave: MISO; Master: MOSI
170+
, Signal dom Bool -- Acknowledge start of transfer
171+
, Signal dom (Maybe (Vec inW (BitVector n)))
166172
)
167173
spiCommon mode ssI msI sckI dinI =
168174
mooreB go cvt ( 0 :: Index n -- cntR
@@ -176,13 +182,16 @@ spiCommon mode ssI msI sckI dinI =
176182
(ssI,msI,sckI,dinI)
177183
where
178184
cvt (_,_,_,dataInQ,dataOutQ,ackQ,doneQ) =
179-
( head dataOutQ
185+
( v2bv $ map head dataOutQ
180186
, ackQ
181187
, if doneQ
182-
then Just (pack dataInQ)
188+
then Just (map v2bv dataInQ)
183189
else Nothing
184190
)
185191

192+
go :: (Index n, Bool, Bool, Vec inW (Vec n Bit), Vec outW (Vec n Bit), Bool, Bool)
193+
-> (Bool, BitVector inW, Bool, Vec outW (BitVector n))
194+
-> (Index n, Bool, Bool, Vec inW (Vec n Bit), Vec outW (Vec n Bit), Bool, Bool)
186195
go (cntQ,cntOldQ,sckOldQ,dataInQ,dataOutQ,_,_) (ss,ms,sck,din) =
187196
(cntD,cntOldD,sck,dataInD,dataOutD,ackD,doneD)
188197
where
@@ -191,16 +200,18 @@ spiCommon mode ssI msI sckI dinI =
191200
| sampleSck = if cntQ == maxBound then 0 else cntQ + 1
192201
| otherwise = cntQ
193202

203+
dataInD :: Vec inW (Vec n Bit)
194204
dataInD
195205
| ss = unpack undefined#
196-
| sampleSck = tail @(n-1) dataInQ :< ms
206+
| sampleSck = zipWith (\d m -> tail @(n-1) d :< m) dataInQ (bv2v ms)
197207
| otherwise = dataInQ
198208

209+
dataOutD :: Vec outW (Vec n Bit)
199210
dataOutD
200-
| ss || (sampleOnTrailing mode && sampleSck && cntQ == maxBound) = unpack din
211+
| ss || (sampleOnTrailing mode && sampleSck && cntQ == maxBound) = fmap bv2v din
201212
| shiftSck = if sampleOnTrailing mode && cntQ == 0
202213
then dataOutQ
203-
else tail @(n-1) dataOutQ :< unpack undefined#
214+
else map (\d -> tail @(n-1) d :< unpack undefined#) dataOutQ
204215
| otherwise = dataOutQ
205216

206217
-- The counter is updated during the capture moment
@@ -222,19 +233,23 @@ spiCommon mode ssI msI sckI dinI =
222233

223234
-- | SPI slave configurable SPI mode and tri-state buffer
224235
spiSlave
225-
:: forall n ds dom
226-
. (HiddenClockResetEnable dom, KnownNat n, 1 <= n)
227-
=> SPISlaveConfig ds dom
236+
:: forall n ds dom misoW mosiW
237+
. ( HiddenClockResetEnable dom
238+
, KnownNat n
239+
, 1 <= n
240+
, KnownNat misoW
241+
, KnownNat mosiW )
242+
=> SPISlaveConfig ds dom misoW mosiW
228243
-- ^ Configure SPI mode and tri-state buffer
229-
-> SpiSlaveIn ds dom 1 1
244+
-> SpiSlaveIn ds dom misoW mosiW
230245
-- ^ SPI interface
231-
-> Signal dom (BitVector n)
246+
-> Signal dom (Vec misoW (BitVector n))
232247
-- ^ Data to send from slave to master.
233248
--
234249
-- Input is latched the moment slave select goes low
235-
-> ( SpiSlaveOut ds dom 1 1
250+
-> ( SpiSlaveOut ds dom misoW mosiW
236251
, Signal dom Bool
237-
, Signal dom (Maybe (BitVector n)))
252+
, Signal dom (Maybe (Vec mosiW (BitVector n))) )
238253
-- ^ Parts of the tuple:
239254
--
240255
-- 1. The "out" part of the inout port of the MISO; used only for simulation.
@@ -246,17 +261,46 @@ spiSlave (SPISlaveConfig mode latch buf) (SpiSlaveIn mosi bin sclk ss) din =
246261
let ssL = if latch then delay undefined ss else ss
247262
mosiL = if latch then delay undefined mosi else mosi
248263
sclkL = if latch then delay undefined sclk else sclk
249-
(miso, ack, dout) = spiCommon mode (bitToBool <$> ssL) (head . bv2v <$> mosiL) (bitToBool <$> sclkL) din
264+
(miso, ack, dout) = spiCommon mode (bitToBool <$> ssL) mosiL (bitToBool <$> sclkL) din
250265
bout = buf bin (not . bitToBool <$> ssL) miso
251266
in (SpiSlaveOut bout, ack, dout)
252267

268+
spiSlave1
269+
:: forall n ds dom
270+
. ( HiddenClockResetEnable dom
271+
, KnownNat n
272+
, 1 <= n )
273+
=> SPISlaveConfig ds dom 1 1
274+
-- ^ Configure SPI mode and tri-state buffer
275+
-> SpiSlaveIn ds dom 1 1
276+
-- ^ SPI interface
277+
-> Signal dom (BitVector n)
278+
-- ^ Data to send from slave to master.
279+
--
280+
-- Input is latched the moment slave select goes low
281+
-> ( SpiSlaveOut ds dom 1 1
282+
, Signal dom Bool
283+
, Signal dom (Maybe (BitVector n)) )
284+
-- ^ Parts of the tuple:
285+
--
286+
-- 1. The "out" part of the inout port of the MISO; used only for simulation.
287+
--
288+
-- 2. the acknowledgement for the data sent from the master to the slave.
289+
--
290+
-- 2. (Maybe) the word sent by the master
291+
spiSlave1 config spiIn dout =
292+
let (spiOut, ack, din) = spiSlave config spiIn (singleton <$> dout)
293+
in (spiOut, ack, fmap head <$> din)
294+
253295
-- | SPI master configurable in the SPI mode and clock divider
254296
--
255297
-- Adds latch to MISO line if the (half period) clock divider is
256298
-- set to 2 or higher.
257299
spiMaster
258-
:: forall n halfPeriod waitTime dom
300+
:: forall n halfPeriod waitTime dom misoW mosiW
259301
. ( HiddenClockResetEnable dom
302+
, KnownNat misoW
303+
, KnownNat mosiW
260304
, KnownNat n
261305
, 1 <= n
262306
, 1 <= halfPeriod
@@ -270,14 +314,14 @@ spiMaster
270314
-> SNat waitTime
271315
-- ^ (core clock) cycles between de-asserting slave-select and start of
272316
-- the SPI clock
273-
-> Signal dom (Maybe (BitVector n))
317+
-> Signal dom (Maybe (Vec mosiW (BitVector n)))
274318
-- ^ Data to send from master to slave, transmission starts when receiving
275319
-- /Just/ a value
276-
-> SpiMasterIn dom 1 1
277-
-> ( SpiMasterOut dom 1 1
320+
-> SpiMasterIn dom misoW mosiW
321+
-> ( SpiMasterOut dom misoW mosiW
278322
, Signal dom Bool -- Busy
279323
, Signal dom Bool -- Acknowledge
280-
, Signal dom (Maybe (BitVector n)) -- Data: Slave -> Master
324+
, Signal dom (Maybe (Vec misoW (BitVector n))) -- Data: Slave -> Master
281325
)
282326
-- ^ Parts of the tuple:
283327
--
@@ -288,27 +332,59 @@ spiMaster
288332
-- the data line will be ignored when /True/
289333
-- 5. (Maybe) the word send from the slave to the master
290334
spiMaster mode fN fW din (SpiMasterIn miso) =
291-
let (mosi, ack, dout) = spiCommon mode ssL (head . bv2v <$> misoL) sclkL
292-
(fromMaybe undefined# <$> din)
335+
let (mosi, ack, dout) = spiCommon mode ssL misoL sclkL
336+
(fromMaybe (repeat undefined#) <$> din)
293337
latch = snatToInteger fN /= 1
294338
ssL = if latch then delay undefined ss else ss
295339
misoL = if latch then delay undefined miso else miso
296340
sclkL = if latch then delay undefined sclk else sclk
297341
(ss, sclk, busy) = spiGen mode fN fW din
298-
in (SpiMasterOut (v2bv . singleton <$> mosi) (boolToBit <$> sclk) (boolToBit <$> ss), busy, ack, dout)
342+
in (SpiMasterOut mosi (boolToBit <$> sclk) (boolToBit <$> ss), busy, ack, dout)
343+
344+
-- | SPI master with single-bit MISO and MOSI width.
345+
spiMaster1
346+
:: forall n halfPeriod waitTime dom
347+
. ( HiddenClockResetEnable dom
348+
, KnownNat n
349+
, 1 <= n
350+
, 1 <= halfPeriod
351+
, 1 <= waitTime )
352+
=> SPIMode
353+
-- ^ SPI Mode
354+
-> SNat halfPeriod
355+
-- ^ Clock divider (half period)
356+
--
357+
-- If set to two or higher, the MISO line will be latched
358+
-> SNat waitTime
359+
-- ^ (core clock) cycles between de-asserting slave-select and start of
360+
-- the SPI clock
361+
-> Signal dom (Maybe (BitVector n))
362+
-- ^ Data to send from master to slave, transmission starts when receiving
363+
-- /Just/ a value
364+
-> SpiMasterIn dom 1 1
365+
-> ( SpiMasterOut dom 1 1
366+
, Signal dom Bool -- Busy
367+
, Signal dom Bool -- Acknowledge
368+
, Signal dom (Maybe (BitVector n)) -- Data: Slave -> Master
369+
)
370+
spiMaster1 mode halfPeriod waitTime dout spiIn =
371+
let (spiOut, busy, ack, din) =
372+
spiMaster mode halfPeriod waitTime (fmap singleton <$> dout) spiIn
373+
in (spiOut, busy, ack, fmap head <$> din)
299374

300375
-- | Generate slave select and SCK
301376
spiGen
302-
:: forall n halfPeriod waitTime dom
377+
:: forall n halfPeriod waitTime dom outW
303378
. ( HiddenClockResetEnable dom
304379
, KnownNat n
380+
, KnownNat outW
305381
, 1 <= n
306382
, 1 <= halfPeriod
307383
, 1 <= waitTime )
308384
=> SPIMode
309385
-> SNat halfPeriod
310386
-> SNat waitTime
311-
-> Signal dom (Maybe (BitVector n))
387+
-> Signal dom (Maybe (Vec outW (BitVector n)))
312388
-> ( Signal dom Bool
313389
, Signal dom Bool
314390
, Signal dom Bool
@@ -386,11 +462,11 @@ spiSlaveLatticeSBIO
386462
--
387463
-- 2. (Maybe) the word send by the master
388464
spiSlaveLatticeSBIO mode latchSPI =
389-
spiSlave (SPISlaveConfig mode latchSPI sbioX)
465+
spiSlave1 (SPISlaveConfig mode latchSPI sbioX)
390466
where
391467
sbioX bin en dout = bout
392468
where
393-
(bout,_,_) = sbio 0b101001 bin (pure 0) dout (pure undefined) en
469+
(bout,_,_) = sbio 0b101001 bin (pure 0) (head . bv2v <$> dout) (pure undefined) en
394470

395471

396472
-- | SPI slave configurable SPI mode, using the BB tri-state buffer
@@ -423,8 +499,8 @@ spiSlaveLatticeBB
423499
--
424500
-- 2. (Maybe) the word send by the master
425501
spiSlaveLatticeBB mode latchSPI =
426-
spiSlave (SPISlaveConfig mode latchSPI bbX)
502+
spiSlave1 (SPISlaveConfig mode latchSPI bbX)
427503
where
428504
bbX bin en dout = bout
429505
where
430-
(bout,_) = bidirectionalBuffer (toEnable en) bin dout
506+
(bout,_) = bidirectionalBuffer (toEnable en) bin (head . bv2v <$> dout)

0 commit comments

Comments
 (0)