@@ -10,9 +10,11 @@ module Clash.Cores.SPI
1010 ( SPIMode (.. )
1111 -- * SPI master
1212 , spiMaster
13+ , spiMasterWide
1314 -- * SPI slave
1415 , SPISlaveConfig (.. )
1516 , spiSlave
17+ , spiSlaveWide
1618 -- ** Vendor configured SPI slaves
1719 , spiSlaveLatticeSBIO
1820 , spiSlaveLatticeBB
@@ -83,7 +85,7 @@ sampleOnLeading _ = False
8385sampleOnTrailing :: SPIMode -> Bool
8486sampleOnTrailing = not . sampleOnLeading
8587
86- data SPISlaveConfig ds dom
88+ data SPISlaveConfig ds dom inW outW
8789 = SPISlaveConfig
8890 { spiSlaveConfigMode :: SPIMode
8991 -- ^ SPI mode
@@ -97,30 +99,34 @@ data SPISlaveConfig ds dom
9799 --
98100 -- * Set to /False/ when core clock is twice as fast, or as fast, as the SCK
99101 , spiSlaveConfigBuffer
100- :: BiSignalIn ds dom 1
102+ :: BiSignalIn ds dom inW
101103 -> Signal dom Bool
102- -> Signal dom Bit
103- -> BiSignalOut ds dom 1
104+ -> Signal dom ( BitVector outW )
105+ -> BiSignalOut ds dom outW
104106 -- ^ Tri-state buffer: first argument is the inout pin, second
105107 -- argument is the output enable, third argument is the value to
106108 -- output when the enable is high
107109 }
108110
109111-- | SPI capture and shift logic that is shared between slave and master
110112spiCommon
111- :: forall n dom
112- . (HiddenClockResetEnable dom , KnownNat n , 1 <= n )
113+ :: forall n dom inW outW
114+ . ( HiddenClockResetEnable dom
115+ , KnownNat inW
116+ , KnownNat outW
117+ , KnownNat n
118+ , 1 <= n )
113119 => SPIMode
114120 -> Signal dom Bool
115121 -- ^ Slave select
116- -> Signal dom Bit
122+ -> Signal dom ( BitVector inW )
117123 -- ^ Slave: MOSI; Master: MISO
118124 -> Signal dom Bool
119125 -- ^ SCK
120- -> Signal dom (BitVector n )
121- -> ( Signal dom Bit -- Slave: MISO; Master: MOSI
122- , Signal dom Bool -- Acknowledge start of transfer
123- , Signal dom (Maybe (BitVector n ))
126+ -> Signal dom (Vec outW ( BitVector n ) )
127+ -> ( Signal dom ( BitVector outW ) -- Slave: MISO; Master: MOSI
128+ , Signal dom Bool -- Acknowledge start of transfer
129+ , Signal dom (Maybe (Vec inW ( BitVector n ) ))
124130 )
125131spiCommon mode ssI msI sckI dinI =
126132 mooreB go cvt ( 0 :: Index n -- cntR
@@ -134,13 +140,16 @@ spiCommon mode ssI msI sckI dinI =
134140 (ssI,msI,sckI,dinI)
135141 where
136142 cvt (_,_,_,dataInQ,dataOutQ,ackQ,doneQ) =
137- ( head dataOutQ
143+ ( v2bv $ map head dataOutQ
138144 , ackQ
139145 , if doneQ
140- then Just (pack dataInQ)
146+ then Just (map v2bv dataInQ)
141147 else Nothing
142148 )
143149
150+ go :: (Index n , Bool , Bool , Vec inW (Vec n Bit ), Vec outW (Vec n Bit ), Bool , Bool )
151+ -> (Bool , BitVector inW , Bool , Vec outW (BitVector n ))
152+ -> (Index n , Bool , Bool , Vec inW (Vec n Bit ), Vec outW (Vec n Bit ), Bool , Bool )
144153 go (cntQ,cntOldQ,sckOldQ,dataInQ,dataOutQ,_,_) (ss,ms,sck,din) =
145154 (cntD,cntOldD,sck,dataInD,dataOutD,ackD,doneD)
146155 where
@@ -149,16 +158,18 @@ spiCommon mode ssI msI sckI dinI =
149158 | sampleSck = if cntQ == maxBound then 0 else cntQ + 1
150159 | otherwise = cntQ
151160
161+ dataInD :: Vec inW (Vec n Bit )
152162 dataInD
153163 | ss = unpack undefined #
154- | sampleSck = tail @ (n - 1 ) dataInQ :< ms
164+ | sampleSck = zipWith ( \ d m -> tail @ (n - 1 ) d :< m) dataInQ (bv2v ms)
155165 | otherwise = dataInQ
156166
167+ dataOutD :: Vec outW (Vec n Bit )
157168 dataOutD
158- | ss || (sampleOnTrailing mode && sampleSck && cntQ == maxBound ) = unpack din
169+ | ss || (sampleOnTrailing mode && sampleSck && cntQ == maxBound ) = fmap bv2v din
159170 | shiftSck = if sampleOnTrailing mode && cntQ == 0
160171 then dataOutQ
161- else tail @ (n - 1 ) dataOutQ :< unpack undefined #
172+ else map ( \ d -> tail @ (n - 1 ) d :< unpack undefined # ) dataOutQ
162173 | otherwise = dataOutQ
163174
164175 -- The counter is updated during the capture moment
@@ -181,8 +192,10 @@ spiCommon mode ssI msI sckI dinI =
181192-- | SPI slave configurable SPI mode and tri-state buffer
182193spiSlave
183194 :: forall n ds dom
184- . (HiddenClockResetEnable dom , KnownNat n , 1 <= n )
185- => SPISlaveConfig ds dom
195+ . ( HiddenClockResetEnable dom
196+ , KnownNat n
197+ , 1 <= n )
198+ => SPISlaveConfig ds dom 1 1
186199 -- ^ Configure SPI mode and tri-state buffer
187200 -> Signal dom Bool
188201 -- ^ Serial Clock (SCLK)
@@ -206,7 +219,44 @@ spiSlave
206219 -- 1. The "out" part of the inout port of the MISO; used only for simulation.
207220 --
208221 -- 2. (Maybe) the word send by the master
209- spiSlave (SPISlaveConfig mode latch buf) sclk mosi bin ss din =
222+ spiSlave cfg sclk mosi bin ss din =
223+ unp $ spiSlaveWide cfg sclk (fmap pack mosi) bin ss (fmap singleton din)
224+ where
225+ unp (a,b,c) = (a, b, fmap (fmap pack) c)
226+
227+ -- | SPI slave configurable SPI mode, MOSI/MISO lane count, and tri-state buffer
228+ spiSlaveWide
229+ :: forall n ds dom mosiW misoW
230+ . ( HiddenClockResetEnable dom
231+ , KnownNat mosiW
232+ , KnownNat misoW
233+ , KnownNat n
234+ , 1 <= n )
235+ => SPISlaveConfig ds dom misoW mosiW
236+ -- ^ Configure SPI mode and tri-state buffer
237+ -> Signal dom Bool
238+ -- ^ Serial Clock (SCLK)
239+ -> Signal dom (BitVector mosiW )
240+ -- ^ Master Output Slave Input (MOSI)
241+ -> BiSignalIn ds dom misoW
242+ -- ^ Master Input Slave Output (MISO)
243+ --
244+ -- Inout port connected to the tri-state buffer for the MISO
245+ -> Signal dom Bool
246+ -- ^ Slave select (SS)
247+ -> Signal dom (Vec mosiW (BitVector n ))
248+ -- ^ Data to send from master to slave
249+ --
250+ -- Input is latched the moment slave select goes low
251+ -> ( BiSignalOut ds dom mosiW
252+ , Signal dom Bool
253+ , Signal dom (Maybe (Vec mosiW (BitVector n ))))
254+ -- ^ Parts of the tuple:
255+ --
256+ -- 1. The "out" part of the inout port of the MISO; used only for simulation.
257+ --
258+ -- 2. (Maybe) the word send by the master
259+ spiSlaveWide (SPISlaveConfig mode latch buf) sclk mosi bin ss din =
210260 let ssL = if latch then delay undefined ss else ss
211261 mosiL = if latch then delay undefined mosi else mosi
212262 sclkL = if latch then delay undefined sclk else sclk
@@ -255,8 +305,56 @@ spiMaster
255305 -- the data line will be ignored when /True/
256306 -- 5. (Maybe) the word send from the slave to the master
257307spiMaster mode fN fW din miso =
308+ unp $ spiMasterWide mode fN fW (fmap (fmap unpack) din) (fmap pack miso)
309+ where
310+ unp (a, b, c, d, e, f) =
311+ (a, fmap unpack b, c, d, e, fmap (fmap pack) f )
312+
313+ -- | SPI master configurable in the SPI mode, MISO/MOSI lane count, and clock divider
314+ --
315+ -- Adds latch to MISO line if the (half period) clock divider is
316+ -- set to 2 or higher.
317+ spiMasterWide
318+ :: forall n halfPeriod waitTime dom misoW mosiW
319+ . ( HiddenClockResetEnable dom
320+ , KnownNat misoW
321+ , KnownNat mosiW
322+ , KnownNat n
323+ , 1 <= n
324+ , 1 <= halfPeriod
325+ , 1 <= waitTime )
326+ => SPIMode
327+ -- ^ SPI Mode
328+ -> SNat halfPeriod
329+ -- ^ Clock divider (half period)
330+ --
331+ -- If set to two or higher, the MISO line will be latched
332+ -> SNat waitTime
333+ -- ^ (core clock) cycles between de-asserting slave-select and start of
334+ -- the SPI clock
335+ -> Signal dom (Maybe (Vec mosiW (BitVector n )))
336+ -- ^ Data to send from master to slave, transmission starts when receiving
337+ -- /Just/ a value
338+ -> Signal dom (BitVector misoW )
339+ -- ^ Master Input Slave Output (MISO)
340+ -> ( Signal dom Bool -- SCK
341+ , Signal dom (BitVector mosiW ) -- MOSI
342+ , Signal dom Bool -- SS
343+ , Signal dom Bool -- Busy
344+ , Signal dom Bool -- Acknowledge
345+ , Signal dom (Maybe (Vec misoW (BitVector n ))) -- Data: Slave -> Master
346+ )
347+ -- ^ Parts of the tuple:
348+ --
349+ -- 1. Serial Clock (SCLK)
350+ -- 2. Master Output Slave Input (MOSI)
351+ -- 3. Slave select (SS)
352+ -- 4. Busy signal indicating that a transmission is in progress, new words on
353+ -- the data line will be ignored when /True/
354+ -- 5. (Maybe) the word send from the slave to the master
355+ spiMasterWide mode fN fW din miso =
258356 let (mosi, ack, dout) = spiCommon mode ssL misoL sclkL
259- (fromMaybe undefined # <$> din)
357+ (fromMaybe ( repeat undefined # ) <$> din)
260358 latch = snatToInteger fN /= 1
261359 ssL = if latch then delay undefined ss else ss
262360 misoL = if latch then delay undefined miso else miso
@@ -266,16 +364,17 @@ spiMaster mode fN fW din miso =
266364
267365-- | Generate slave select and SCK
268366spiGen
269- :: forall n halfPeriod waitTime dom
367+ :: forall n halfPeriod waitTime dom outW
270368 . ( HiddenClockResetEnable dom
271369 , KnownNat n
370+ , KnownNat outW
272371 , 1 <= n
273372 , 1 <= halfPeriod
274373 , 1 <= waitTime )
275374 => SPIMode
276375 -> SNat halfPeriod
277376 -> SNat waitTime
278- -> Signal dom (Maybe (BitVector n ))
377+ -> Signal dom (Maybe (Vec outW ( BitVector n ) ))
279378 -> ( Signal dom Bool
280379 , Signal dom Bool
281380 , Signal dom Bool
@@ -366,7 +465,7 @@ spiSlaveLatticeSBIO mode latchSPI =
366465 where
367466 sbioX bin en dout = bout
368467 where
369- (bout,_,_) = sbio 0b101001 bin (pure 0 ) dout (pure undefined ) en
468+ (bout,_,_) = sbio 0b101001 bin (pure 0 ) ( fmap unpack dout) (pure undefined ) en
370469
371470
372471-- | SPI slave configurable SPI mode, using the BB tri-state buffer
@@ -412,4 +511,4 @@ spiSlaveLatticeBB mode latchSPI =
412511 where
413512 bbX bin en dout = bout
414513 where
415- (bout,_) = bidirectionalBuffer (toEnable en) bin dout
514+ (bout,_) = bidirectionalBuffer (toEnable en) bin ( fmap unpack dout)
0 commit comments