@@ -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
@@ -134,7 +136,7 @@ sampleOnLeading _ = False
134136sampleOnTrailing :: SPIMode -> Bool
135137sampleOnTrailing = not . sampleOnLeading
136138
137- data SPISlaveConfig ds dom
139+ data SPISlaveConfig ds dom ( misoW :: Nat ) ( mosiW :: Nat )
138140 = SPISlaveConfig
139141 { spiSlaveConfigMode :: SPIMode
140142 -- ^ SPI mode
@@ -148,30 +150,34 @@ data SPISlaveConfig ds dom
148150 --
149151 -- * Set to /False/ when core clock is twice as fast, or as fast, as the SCK
150152 , spiSlaveConfigBuffer
151- :: BiSignalIn ds dom 1
153+ :: BiSignalIn ds dom misoW
152154 -> Signal dom Bool
153- -> Signal dom Bit
154- -> BiSignalOut ds dom 1
155+ -> Signal dom ( BitVector misoW )
156+ -> BiSignalOut ds dom misoW
155157 -- ^ Tri-state buffer: first argument is the inout pin, second
156158 -- argument is the output enable, third argument is the value to
157159 -- output when the enable is high
158160 }
159161
160162-- | SPI capture and shift logic that is shared between slave and master
161163spiCommon
162- :: forall n dom
163- . (HiddenClockResetEnable dom , KnownNat n , 1 <= n )
164+ :: forall n dom inW outW
165+ . ( HiddenClockResetEnable dom
166+ , KnownNat inW
167+ , KnownNat outW
168+ , KnownNat n
169+ , 1 <= n )
164170 => SPIMode
165171 -> Signal dom Bool
166172 -- ^ Slave select
167- -> Signal dom Bit
173+ -> Signal dom ( BitVector inW )
168174 -- ^ Slave: MOSI; Master: MISO
169175 -> Signal dom Bool
170176 -- ^ SCK
171- -> Signal dom (BitVector n )
172- -> ( Signal dom Bit -- Slave: MISO; Master: MOSI
173- , Signal dom Bool -- Acknowledge start of transfer
174- , Signal dom (Maybe (BitVector n ))
177+ -> Signal dom (Vec outW ( BitVector n ) )
178+ -> ( Signal dom ( BitVector outW ) -- Slave: MISO; Master: MOSI
179+ , Signal dom Bool -- Acknowledge start of transfer
180+ , Signal dom (Maybe (Vec inW ( BitVector n ) ))
175181 )
176182spiCommon mode ssI msI sckI dinI =
177183 mooreB go cvt ( 0 :: Index n -- cntR
@@ -185,13 +191,16 @@ spiCommon mode ssI msI sckI dinI =
185191 (ssI,msI,sckI,dinI)
186192 where
187193 cvt (_,_,_,dataInQ,dataOutQ,ackQ,doneQ) =
188- ( head dataOutQ
194+ ( v2bv $ map head dataOutQ
189195 , ackQ
190196 , if doneQ
191- then Just (pack dataInQ)
197+ then Just (map v2bv dataInQ)
192198 else Nothing
193199 )
194200
201+ go :: (Index n , Bool , Bool , Vec inW (Vec n Bit ), Vec outW (Vec n Bit ), Bool , Bool )
202+ -> (Bool , BitVector inW , Bool , Vec outW (BitVector n ))
203+ -> (Index n , Bool , Bool , Vec inW (Vec n Bit ), Vec outW (Vec n Bit ), Bool , Bool )
195204 go (cntQ,cntOldQ,sckOldQ,dataInQ,dataOutQ,_,_) (ss,ms,sck,din) =
196205 (cntD,cntOldD,sck,dataInD,dataOutD,ackD,doneD)
197206 where
@@ -200,16 +209,18 @@ spiCommon mode ssI msI sckI dinI =
200209 | sampleSck = if cntQ == maxBound then 0 else cntQ + 1
201210 | otherwise = cntQ
202211
212+ dataInD :: Vec inW (Vec n Bit )
203213 dataInD
204214 | ss = unpack undefined #
205- | sampleSck = tail @ (n - 1 ) dataInQ :< ms
215+ | sampleSck = zipWith ( \ d m -> tail @ (n - 1 ) d :< m) dataInQ (bv2v ms)
206216 | otherwise = dataInQ
207217
218+ dataOutD :: Vec outW (Vec n Bit )
208219 dataOutD
209- | ss || (sampleOnTrailing mode && sampleSck && cntQ == maxBound ) = unpack din
220+ | ss || (sampleOnTrailing mode && sampleSck && cntQ == maxBound ) = fmap bv2v din
210221 | shiftSck = if sampleOnTrailing mode && cntQ == 0
211222 then dataOutQ
212- else tail @ (n - 1 ) dataOutQ :< unpack undefined #
223+ else map ( \ d -> tail @ (n - 1 ) d :< unpack undefined # ) dataOutQ
213224 | otherwise = dataOutQ
214225
215226 -- The counter is updated during the capture moment
@@ -231,19 +242,23 @@ spiCommon mode ssI msI sckI dinI =
231242
232243-- | SPI slave configurable SPI mode and tri-state buffer
233244spiSlave
234- :: forall n ds dom
235- . (HiddenClockResetEnable dom , KnownNat n , 1 <= n )
236- => SPISlaveConfig ds dom
245+ :: forall n ds dom misoW mosiW
246+ . ( HiddenClockResetEnable dom
247+ , KnownNat n
248+ , 1 <= n
249+ , KnownNat misoW
250+ , KnownNat mosiW )
251+ => SPISlaveConfig ds dom misoW mosiW
237252 -- ^ Configure SPI mode and tri-state buffer
238- -> SpiSlaveIn ds dom 1 1
253+ -> SpiSlaveIn ds dom misoW mosiW
239254 -- ^ SPI interface
240- -> Signal dom (BitVector n )
255+ -> Signal dom (Vec misoW ( BitVector n ) )
241256 -- ^ Data to send from slave to master.
242257 --
243258 -- Input is latched the moment slave select goes low
244- -> ( SpiSlaveOut ds dom 1 1
259+ -> ( SpiSlaveOut ds dom misoW mosiW
245260 , Signal dom Bool
246- , Signal dom (Maybe (BitVector n )))
261+ , Signal dom (Maybe (Vec mosiW ( BitVector n ))) )
247262 -- ^ Parts of the tuple:
248263 --
249264 -- 1. The "out" part of the inout port of the MISO; used only for simulation.
@@ -255,17 +270,46 @@ spiSlave (SPISlaveConfig mode latch buf) (SpiSlaveIn mosi bin sclk ss) din =
255270 let ssL = if latch then delay undefined ss else ss
256271 mosiL = if latch then delay undefined mosi else mosi
257272 sclkL = if latch then delay undefined sclk else sclk
258- (miso, ack, dout) = spiCommon mode (bitToBool <$> ssL) ( head . bv2v <$> mosiL) (bitToBool <$> sclkL) din
273+ (miso, ack, dout) = spiCommon mode (bitToBool <$> ssL) mosiL (bitToBool <$> sclkL) din
259274 bout = buf bin (not . bitToBool <$> ssL) miso
260275 in (SpiSlaveOut bout, ack, dout)
261276
277+ spiSlave1
278+ :: forall n ds dom
279+ . ( HiddenClockResetEnable dom
280+ , KnownNat n
281+ , 1 <= n )
282+ => SPISlaveConfig ds dom 1 1
283+ -- ^ Configure SPI mode and tri-state buffer
284+ -> SpiSlaveIn ds dom 1 1
285+ -- ^ SPI interface
286+ -> Signal dom (BitVector n )
287+ -- ^ Data to send from slave to master.
288+ --
289+ -- Input is latched the moment slave select goes low
290+ -> ( SpiSlaveOut ds dom 1 1
291+ , Signal dom Bool
292+ , Signal dom (Maybe (BitVector n )) )
293+ -- ^ Parts of the tuple:
294+ --
295+ -- 1. The "out" part of the inout port of the MISO; used only for simulation.
296+ --
297+ -- 2. the acknowledgement for the data sent from the master to the slave.
298+ --
299+ -- 2. (Maybe) the word sent by the master
300+ spiSlave1 config spiIn dout =
301+ let (spiOut, ack, din) = spiSlave config spiIn (singleton <$> dout)
302+ in (spiOut, ack, fmap head <$> din)
303+
262304-- | SPI master configurable in the SPI mode and clock divider
263305--
264306-- Adds latch to MISO line if the (half period) clock divider is
265307-- set to 2 or higher.
266308spiMaster
267- :: forall n halfPeriod waitTime dom
309+ :: forall n halfPeriod waitTime dom misoW mosiW
268310 . ( HiddenClockResetEnable dom
311+ , KnownNat misoW
312+ , KnownNat mosiW
269313 , KnownNat n
270314 , 1 <= n
271315 , 1 <= halfPeriod
@@ -279,14 +323,14 @@ spiMaster
279323 -> SNat waitTime
280324 -- ^ (core clock) cycles between de-asserting slave-select and start of
281325 -- the SPI clock
282- -> Signal dom (Maybe (BitVector n ))
326+ -> Signal dom (Maybe (Vec mosiW ( BitVector n ) ))
283327 -- ^ Data to send from master to slave, transmission starts when receiving
284328 -- /Just/ a value
285- -> SpiMasterIn dom 1 1
286- -> ( SpiMasterOut dom 1 1
329+ -> SpiMasterIn dom misoW mosiW
330+ -> ( SpiMasterOut dom misoW mosiW
287331 , Signal dom Bool -- Busy
288332 , Signal dom Bool -- Acknowledge
289- , Signal dom (Maybe (BitVector n )) -- Data: Slave -> Master
333+ , Signal dom (Maybe (Vec misoW ( BitVector n ) )) -- Data: Slave -> Master
290334 )
291335 -- ^ Parts of the tuple:
292336 --
@@ -297,27 +341,59 @@ spiMaster
297341 -- the data line will be ignored when /True/
298342 -- 5. (Maybe) the word send from the slave to the master
299343spiMaster mode fN fW din (SpiMasterIn miso) =
300- let (mosi, ack, dout) = spiCommon mode ssL ( head . bv2v <$> misoL) sclkL
301- (fromMaybe undefined # <$> din)
344+ let (mosi, ack, dout) = spiCommon mode ssL misoL sclkL
345+ (fromMaybe ( repeat undefined # ) <$> din)
302346 latch = snatToInteger fN /= 1
303347 ssL = if latch then delay undefined ss else ss
304348 misoL = if latch then delay undefined miso else miso
305349 sclkL = if latch then delay undefined sclk else sclk
306350 (ss, sclk, busy) = spiGen mode fN fW din
307- in (SpiMasterOut (v2bv . singleton <$> mosi) (boolToBit <$> sclk) (boolToBit <$> ss), busy, ack, dout)
351+ in (SpiMasterOut mosi (boolToBit <$> sclk) (boolToBit <$> ss), busy, ack, dout)
352+
353+ -- | SPI master with single-bit MISO and MOSI width.
354+ spiMaster1
355+ :: forall n halfPeriod waitTime dom
356+ . ( HiddenClockResetEnable dom
357+ , KnownNat n
358+ , 1 <= n
359+ , 1 <= halfPeriod
360+ , 1 <= waitTime )
361+ => SPIMode
362+ -- ^ SPI Mode
363+ -> SNat halfPeriod
364+ -- ^ Clock divider (half period)
365+ --
366+ -- If set to two or higher, the MISO line will be latched
367+ -> SNat waitTime
368+ -- ^ (core clock) cycles between de-asserting slave-select and start of
369+ -- the SPI clock
370+ -> Signal dom (Maybe (BitVector n ))
371+ -- ^ Data to send from master to slave, transmission starts when receiving
372+ -- /Just/ a value
373+ -> SpiMasterIn dom 1 1
374+ -> ( SpiMasterOut dom 1 1
375+ , Signal dom Bool -- Busy
376+ , Signal dom Bool -- Acknowledge
377+ , Signal dom (Maybe (BitVector n )) -- Data: Slave -> Master
378+ )
379+ spiMaster1 mode halfPeriod waitTime dout spiIn =
380+ let (spiOut, busy, ack, din) =
381+ spiMaster mode halfPeriod waitTime (fmap singleton <$> dout) spiIn
382+ in (spiOut, busy, ack, fmap head <$> din)
308383
309384-- | Generate slave select and SCK
310385spiGen
311- :: forall n halfPeriod waitTime dom
386+ :: forall n halfPeriod waitTime dom outW
312387 . ( HiddenClockResetEnable dom
313388 , KnownNat n
389+ , KnownNat outW
314390 , 1 <= n
315391 , 1 <= halfPeriod
316392 , 1 <= waitTime )
317393 => SPIMode
318394 -> SNat halfPeriod
319395 -> SNat waitTime
320- -> Signal dom (Maybe (BitVector n ))
396+ -> Signal dom (Maybe (Vec outW ( BitVector n ) ))
321397 -> ( Signal dom Bool
322398 , Signal dom Bool
323399 , Signal dom Bool
@@ -395,11 +471,11 @@ spiSlaveLatticeSBIO
395471 --
396472 -- 2. (Maybe) the word send by the master
397473spiSlaveLatticeSBIO mode latchSPI =
398- spiSlave (SPISlaveConfig mode latchSPI sbioX)
474+ spiSlave1 (SPISlaveConfig mode latchSPI sbioX)
399475 where
400476 sbioX bin en dout = bout
401477 where
402- (bout,_,_) = sbio 0b101001 bin (pure 0 ) dout (pure undefined ) en
478+ (bout,_,_) = sbio 0b101001 bin (pure 0 ) ( head . bv2v <$> dout) (pure undefined ) en
403479
404480
405481-- | SPI slave configurable SPI mode, using the BB tri-state buffer
@@ -432,8 +508,8 @@ spiSlaveLatticeBB
432508 --
433509 -- 2. (Maybe) the word send by the master
434510spiSlaveLatticeBB mode latchSPI =
435- spiSlave (SPISlaveConfig mode latchSPI bbX)
511+ spiSlave1 (SPISlaveConfig mode latchSPI bbX)
436512 where
437513 bbX bin en dout = bout
438514 where
439- (bout,_) = bidirectionalBuffer (toEnable en) bin dout
515+ (bout,_) = bidirectionalBuffer (toEnable en) bin ( head . bv2v <$> dout)
0 commit comments